| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.MongoDB.Query
Contents
Description
Query and update documents
Synopsis
- type Action = ReaderT MongoContext
- access :: MonadIO m => Pipe -> AccessMode -> Database -> Action m a -> m a
- data Failure
- type ErrorCode = Int
- data AccessMode
- type GetLastError = Document
- master :: AccessMode
- slaveOk :: AccessMode
- accessMode :: Monad m => AccessMode -> Action m a -> Action m a
- liftDB :: (MonadReader env m, HasMongoContext env, MonadIO m) => Action IO a -> m a
- data MongoContext = MongoContext {}
- class HasMongoContext env where- mongoContext :: env -> MongoContext
 
- type Database = Text
- allDatabases :: MonadIO m => Action m [Database]
- useDb :: Monad m => Database -> Action m a -> Action m a
- thisDatabase :: Monad m => Action m Database
- type Username = Text
- type Password = Text
- auth :: MonadIO m => Username -> Password -> Action m Bool
- authMongoCR :: MonadIO m => Username -> Password -> Action m Bool
- authSCRAMSHA1 :: MonadIO m => Username -> Password -> Action m Bool
- type Collection = Text
- allCollections :: MonadIO m => Action m [Collection]
- data Selection = Select {- selector :: Selector
- coll :: Collection
 
- type Selector = Document
- whereJS :: Selector -> Javascript -> Selector
- class Select aQueryOrSelection where- select :: Selector -> Collection -> aQueryOrSelection
 
- insert :: MonadIO m => Collection -> Document -> Action m Value
- insert_ :: MonadIO m => Collection -> Document -> Action m ()
- insertMany :: MonadIO m => Collection -> [Document] -> Action m [Value]
- insertMany_ :: MonadIO m => Collection -> [Document] -> Action m ()
- insertAll :: MonadIO m => Collection -> [Document] -> Action m [Value]
- insertAll_ :: MonadIO m => Collection -> [Document] -> Action m ()
- save :: MonadIO m => Collection -> Document -> Action m ()
- replace :: MonadIO m => Selection -> Document -> Action m ()
- repsert :: MonadIO m => Selection -> Document -> Action m ()
- upsert :: MonadIO m => Selection -> Document -> Action m ()
- type Modifier = Document
- modify :: MonadIO m => Selection -> Modifier -> Action m ()
- updateMany :: MonadIO m => Collection -> [(Selector, Document, [UpdateOption])] -> Action m WriteResult
- updateAll :: MonadIO m => Collection -> [(Selector, Document, [UpdateOption])] -> Action m WriteResult
- data WriteResult = WriteResult {}
- data UpdateOption
- data Upserted = Upserted {}
- delete :: MonadIO m => Selection -> Action m ()
- deleteOne :: MonadIO m => Selection -> Action m ()
- deleteMany :: MonadIO m => Collection -> [(Selector, [DeleteOption])] -> Action m WriteResult
- deleteAll :: MonadIO m => Collection -> [(Selector, [DeleteOption])] -> Action m WriteResult
- data DeleteOption = SingleRemove
- data Query = Query {}
- data QueryOption
- type Projector = Document
- type Limit = Word32
- type Order = Document
- type BatchSize = Word32
- explain :: MonadIO m => Query -> Action m Document
- find :: MonadIO m => Query -> Action m Cursor
- findOne :: MonadIO m => Query -> Action m (Maybe Document)
- fetch :: MonadIO m => Query -> Action m Document
- findAndModify :: (MonadIO m, MonadFail m) => Query -> Document -> Action m (Either String Document)
- findAndModifyOpts :: (MonadIO m, MonadFail m) => Query -> FindAndModifyOpts -> Action m (Either String (Maybe Document))
- data FindAndModifyOpts
- defFamUpdateOpts :: Document -> FindAndModifyOpts
- count :: MonadIO m => Query -> Action m Int
- distinct :: MonadIO m => Label -> Selection -> Action m [Value]
- data Cursor
- nextBatch :: MonadIO m => Cursor -> Action m [Document]
- next :: MonadIO m => Cursor -> Action m (Maybe Document)
- nextN :: MonadIO m => Int -> Cursor -> Action m [Document]
- rest :: MonadIO m => Cursor -> Action m [Document]
- closeCursor :: MonadIO m => Cursor -> Action m ()
- isCursorClosed :: MonadIO m => Cursor -> Action m Bool
- type Pipeline = [Document]
- data AggregateConfig = AggregateConfig {
- aggregate :: (MonadIO m, MonadFail m) => Collection -> Pipeline -> Action m [Document]
- aggregateCursor :: (MonadIO m, MonadFail m) => Collection -> Pipeline -> AggregateConfig -> Action m Cursor
- data Group = Group {- gColl :: Collection
- gKey :: GroupKey
- gReduce :: Javascript
- gInitial :: Document
- gCond :: Selector
- gFinalize :: Maybe Javascript
 
- data GroupKey- = Key [Label]
- | KeyF Javascript
 
- group :: MonadIO m => Group -> Action m [Document]
- data MapReduce = MapReduce {}
- type MapFun = Javascript
- type ReduceFun = Javascript
- type FinalizeFun = Javascript
- data MROut
- data MRMerge
- type MRResult = Document
- mapReduce :: Collection -> MapFun -> ReduceFun -> MapReduce
- runMR :: MonadIO m => MapReduce -> Action m Cursor
- runMR' :: MonadIO m => MapReduce -> Action m MRResult
- type Command = Document
- runCommand :: MonadIO m => Command -> Action m Document
- runCommand1 :: MonadIO m => Text -> Action m Document
- eval :: (MonadIO m, Val v) => Javascript -> Action m v
- retrieveServerData :: MonadIO m => Action m ServerData
- data ServerData = ServerData {}
Monad
type Action = ReaderT MongoContext Source #
A monad on top of m (which must be a MonadIO) that may access the database and may fail with a DB Failure
access :: MonadIO m => Pipe -> AccessMode -> Database -> Action m a -> m a Source #
Run action against database on server at other end of pipe. Use access mode for any reads and writes.
 Throw Failure in case of any error.
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.
Constructors
| 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 ErrorCode String | Query failed for some reason as described in the string | 
| WriteFailure Int ErrorCode String | Error observed by getLastError after a write, error description is in string, index of failed document is the first argument | 
| WriteConcernFailure Int String | Write concern error. It's reported only by insert, update, delete commands. Not by wire protocol. | 
| DocNotFound Selection | 
 | 
| AggregateFailure String | 
 | 
| CompoundFailure [Failure] | When we need to aggregate several failures and report them. | 
| ProtocolFailure Int String | The structure of the returned documents doesn't match what we expected | 
Instances
| Eq Failure Source # | |
| Show Failure Source # | |
| Exception Failure Source # | |
| Defined in Database.MongoDB.Query Methods toException :: Failure -> SomeException # fromException :: SomeException -> Maybe Failure # displayException :: Failure -> String # | |
data AccessMode Source #
Type of reads and writes to perform
Constructors
| ReadStaleOk | Read-only action, reading stale data from a slave is OK. | 
| UnconfirmedWrites | Read-write action, slave not OK, every write is fire & forget. | 
| ConfirmWrites GetLastError | Read-write action, slave not OK, every write is confirmed with getLastError. | 
Instances
| Show AccessMode Source # | |
| Defined in Database.MongoDB.Query Methods showsPrec :: Int -> AccessMode -> ShowS # show :: AccessMode -> String # showList :: [AccessMode] -> ShowS # | |
type GetLastError = Document Source #
Parameters for getLastError command. For example ["w" =: 2] tells the server to wait for the write to reach at least two servers in replica set before acknowledging. See http://www.mongodb.org/display/DOCS/Last+Error+Commands for more options.
master :: AccessMode Source #
Same as ConfirmWrites []
slaveOk :: AccessMode Source #
Same as ReadStaleOk
accessMode :: Monad m => AccessMode -> Action m a -> Action m a Source #
Run action with given AccessMode
liftDB :: (MonadReader env m, HasMongoContext env, MonadIO m) => Action IO a -> m a Source #
data MongoContext Source #
Values needed when executing a db operation
Constructors
| MongoContext | operations query/update this database | 
| Fields 
 | |
Instances
| HasMongoContext MongoContext Source # | |
| Defined in Database.MongoDB.Query Methods | |
class HasMongoContext env where Source #
Methods
mongoContext :: env -> MongoContext Source #
Instances
| HasMongoContext MongoContext Source # | |
| Defined in Database.MongoDB.Query Methods | |
Database
Authentication
auth :: MonadIO m => Username -> Password -> Action m Bool Source #
Authenticate with the current database (if server is running in secure mode). Return whether authentication was successful or not. Reauthentication is required for every new pipe. SCRAM-SHA-1 will be used for server versions 3.0+, MONGO-CR for lower versions.
authMongoCR :: MonadIO m => Username -> Password -> Action m Bool Source #
Authenticate with the current database, using the MongoDB-CR authentication mechanism (default in MongoDB server < 3.0)
authSCRAMSHA1 :: MonadIO m => Username -> Password -> Action m Bool Source #
Authenticate with the current database, using the SCRAM-SHA-1 authentication mechanism (default in MongoDB server >= 3.0)
Collection
type Collection = Text Source #
Collection name (not prefixed with database)
allCollections :: MonadIO m => Action m [Collection] Source #
List all collections in this database
Selection
Selects documents in collection that match selector
Constructors
| Select | |
| Fields 
 | |
type Selector = Document Source #
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 -> Selector Source #
Add Javascript predicate to selector, in which case a document must match both selector and predicate
class Select aQueryOrSelection where Source #
Methods
select :: Selector -> Collection -> aQueryOrSelection Source #
Write
Insert
insert :: MonadIO m => Collection -> Document -> Action m Value Source #
Insert document into collection and return its "_id" value, which is created automatically if not supplied
insert_ :: MonadIO m => Collection -> Document -> Action m () Source #
Same as insert except don't return _id
insertMany :: MonadIO m => Collection -> [Document] -> Action m [Value] Source #
Insert documents into collection and return their "_id" values, which are created automatically if not supplied. If a document fails to be inserted (eg. due to duplicate key) then remaining docs are aborted, and LastError is set. An exception will be throw if any error occurs.
insertMany_ :: MonadIO m => Collection -> [Document] -> Action m () Source #
Same as insertMany except don't return _ids
insertAll :: MonadIO m => Collection -> [Document] -> Action m [Value] Source #
Insert documents into collection and return their "_id" values, which are created automatically if not supplied. If a document fails to be inserted (eg. due to duplicate key) then remaining docs are still inserted.
insertAll_ :: MonadIO m => Collection -> [Document] -> Action m () Source #
Same as insertAll except don't return _ids
Update
save :: MonadIO m => Collection -> Document -> Action m () Source #
Save document to collection, meaning insert it if its new (has no "_id" field) or upsert it if its not new (has "_id" field)
replace :: MonadIO m => Selection -> Document -> Action m () Source #
Replace first document in selection with given document
repsert :: MonadIO m => Selection -> Document -> Action m () Source #
Deprecated: use upsert instead
Replace first document in selection with given document, or insert document if selection is empty
upsert :: MonadIO m => Selection -> Document -> Action m () Source #
Update first document in selection with given document, or insert document if selection is empty
type Modifier = Document Source #
Update operations on fields in a document. See https://docs.mongodb.com/manual/reference/operator/update/
modify :: MonadIO m => Selection -> Modifier -> Action m () Source #
Update all documents in selection using given modifier
updateMany :: MonadIO m => Collection -> [(Selector, Document, [UpdateOption])] -> Action m WriteResult Source #
Bulk update operation. If one update fails it will not update the remaining - documents. Current returned value is only a place holder. With mongodb server - before 2.6 it will send update requests one by one. In order to receive - error messages in versions under 2.6 you need to user confirmed writes. - Otherwise even if the errors had place the list of errors will be empty and - the result will be success. After 2.6 it will use bulk update feature in - mongodb.
updateAll :: MonadIO m => Collection -> [(Selector, Document, [UpdateOption])] -> Action m WriteResult Source #
Bulk update operation. If one update fails it will proceed with the - remaining documents. With mongodb server before 2.6 it will send update - requests one by one. In order to receive error messages in versions under - 2.6 you need to use confirmed writes. Otherwise even if the errors had - place the list of errors will be empty and the result will be success. - After 2.6 it will use bulk update feature in mongodb.
data WriteResult Source #
Constructors
| WriteResult | |
| Fields | |
Instances
| Show WriteResult Source # | |
| Defined in Database.MongoDB.Query Methods showsPrec :: Int -> WriteResult -> ShowS # show :: WriteResult -> String # showList :: [WriteResult] -> ShowS # | |
data UpdateOption Source #
Constructors
| Upsert | If set, the database will insert the supplied object into the collection if no matching document is found | 
| MultiUpdate | If set, the database will update all matching objects in the collection. Otherwise only updates first matching doc | 
Instances
| Eq UpdateOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol | |
| Show UpdateOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol Methods showsPrec :: Int -> UpdateOption -> ShowS # show :: UpdateOption -> String # showList :: [UpdateOption] -> ShowS # | |
Constructors
| Upserted | |
| Fields 
 | |
Delete
deleteMany :: MonadIO m => Collection -> [(Selector, [DeleteOption])] -> Action m WriteResult Source #
Bulk delete operation. If one delete fails it will not delete the remaining - documents. Current returned value is only a place holder. With mongodb server - before 2.6 it will send delete requests one by one. After 2.6 it will use - bulk delete feature in mongodb.
deleteAll :: MonadIO m => Collection -> [(Selector, [DeleteOption])] -> Action m WriteResult Source #
Bulk delete operation. If one delete fails it will proceed with the - remaining documents. Current returned value is only a place holder. With - mongodb server before 2.6 it will send delete requests one by one. After 2.6 - it will use bulk delete feature in mongodb.
data DeleteOption Source #
Constructors
| SingleRemove | If set, the database will remove only the first matching document in the collection. Otherwise all matching documents will be removed | 
Instances
| Eq DeleteOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol | |
| Show DeleteOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol Methods showsPrec :: Int -> DeleteOption -> ShowS # show :: DeleteOption -> String # showList :: [DeleteOption] -> ShowS # | |
Read
Query
Use select to create a basic query with defaults, then modify if desired. For example, (select sel col) {limit = 10}
Constructors
| Query | |
| Fields 
 | |
data QueryOption Source #
Constructors
| 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 | The server normally times out idle cursors after 10 minutes to prevent a memory leak in case a client forgets to close a cursor. Set this option to allow a cursor to live forever until it is closed. | 
| 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.
  | Exhaust  -- ^ Stream the data down full blast in multiple "more" packages, on the assumption that the client will fully read all data queried. Faster when you are pulling a lot of data and know you want to pull it all down. Note: the client is not allowed to not read all the data unless it closes the connection.
 Exhaust commented out because not compatible with current  | 
| Partial | Get partial results from a _mongos_ if some shards are down, instead of throwing an error. | 
Instances
| Eq QueryOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol | |
| Show QueryOption Source # | |
| Defined in Database.MongoDB.Internal.Protocol Methods showsPrec :: Int -> QueryOption -> ShowS # show :: QueryOption -> String # showList :: [QueryOption] -> ShowS # | |
type Projector = Document Source #
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.
type Order = Document Source #
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 = Word32 Source #
The number of document to return in each batch response from the server. 0 means use Mongo default.
explain :: MonadIO m => Query -> Action m Document Source #
Return performance stats of query execution
findOne :: MonadIO m => Query -> Action m (Maybe Document) Source #
Fetch first document satisfying query or Nothing if none satisfy it
fetch :: MonadIO m => Query -> Action m Document Source #
Same as findOne except throw DocNotFound if none match
Arguments
| :: (MonadIO m, MonadFail m) | |
| => Query | |
| -> Document | updates | 
| -> Action m (Either String Document) | 
runs the findAndModify command as an update without an upsert and new set to true. Returns a single updated document (new option is set to true).
see findAndModifyOpts if you want to use findAndModify in a differnt way
findAndModifyOpts :: (MonadIO m, MonadFail m) => Query -> FindAndModifyOpts -> Action m (Either String (Maybe Document)) Source #
runs the findAndModify command,
 allows more options than findAndModify
data FindAndModifyOpts Source #
Instances
| Show FindAndModifyOpts Source # | |
| Defined in Database.MongoDB.Query Methods showsPrec :: Int -> FindAndModifyOpts -> ShowS # show :: FindAndModifyOpts -> String # showList :: [FindAndModifyOpts] -> ShowS # | |
count :: MonadIO m => Query -> Action m Int Source #
Fetch number of documents satisfying query (including effect of skip and/or limit if present)
distinct :: MonadIO m => Label -> Selection -> Action 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.
nextBatch :: MonadIO m => Cursor -> Action m [Document] Source #
Return next batch of documents in query result, which will be empty if finished.
next :: MonadIO m => Cursor -> Action m (Maybe Document) Source #
Return next document in query result, or Nothing if finished.
nextN :: MonadIO m => Int -> Cursor -> Action m [Document] Source #
Return next N documents or less if end is reached
rest :: MonadIO m => Cursor -> Action m [Document] Source #
Return remaining documents in query result
Aggregate
data AggregateConfig Source #
Constructors
| AggregateConfig | |
Instances
| Show AggregateConfig Source # | |
| Defined in Database.MongoDB.Query Methods showsPrec :: Int -> AggregateConfig -> ShowS # show :: AggregateConfig -> String # showList :: [AggregateConfig] -> ShowS # | |
| Default AggregateConfig Source # | |
| Defined in Database.MongoDB.Query Methods def :: AggregateConfig # | |
aggregate :: (MonadIO m, MonadFail m) => Collection -> Pipeline -> Action m [Document] Source #
Runs an aggregate and unpacks the result. See http://docs.mongodb.org/manual/core/aggregation/ for details.
aggregateCursor :: (MonadIO m, MonadFail m) => Collection -> Pipeline -> AggregateConfig -> Action m Cursor Source #
Runs an aggregate and unpacks the result. See http://docs.mongodb.org/manual/core/aggregation/ for details.
Group
Groups documents in collection by key then reduces (aggregates) each group
Constructors
| Group | |
| Fields 
 | |
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 | 
group :: MonadIO m => Group -> Action 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. This implements the latest version of map-reduce that requires MongoDB 1.7.4 or greater. To map-reduce against an older server use runCommand directly as described in http://www.mongodb.org/display/DOCS/MapReduce.
Constructors
| MapReduce | |
| Fields 
 | |
type MapFun = Javascript Source #
() -> 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 = Javascript Source #
(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 = Javascript Source #
(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.
Constructors
| Inline | Return results directly instead of writing them to an output collection. Results must fit within 16MB limit of a single document | 
| Output MRMerge Collection (Maybe Database) | Write results to given collection, in other database if specified. Follow merge policy when entry already exists | 
Constructors
| Replace | Clear all old data and replace it with new data | 
| Merge | Leave old data but overwrite entries with the same key with new data | 
| Reduce | Leave old data but combine entries with the same key via MR's reduce function | 
type MRResult = Document Source #
Result of running a MapReduce has some stats besides the output. See http://www.mongodb.org/display/DOCS/MapReduce#MapReduce-Resultobject
mapReduce :: Collection -> MapFun -> ReduceFun -> MapReduce Source #
MapReduce on collection with given map and reduce functions. Remaining attributes are set to their defaults, which are stated in their comments.
runMR :: MonadIO m => MapReduce -> Action m Cursor Source #
Run MapReduce and return cursor of results. Error if map/reduce fails (because of bad Javascript)
runMR' :: MonadIO m => MapReduce -> Action m MRResult Source #
Run MapReduce and return a MR result document containing stats and the results if Inlined. Error if the map/reduce failed (because of bad Javascript).
Command
type Command = Document Source #
A command is a special query or action against the database. See http://www.mongodb.org/display/DOCS/Commands for details.
runCommand :: MonadIO m => Command -> Action m Document Source #
Run command against the database and return its result
runCommand1 :: MonadIO m => Text -> Action m Document Source #
runCommand1 foo = runCommand [foo =: 1]
retrieveServerData :: MonadIO m => Action m ServerData Source #
data ServerData Source #
Constructors
| ServerData | |
| Fields 
 | |