Wrapper for mongoc_collection_t.

mongoc_collection_t provides access to a MongoDB collection. This handle is useful for actions for most CRUD operations, I.e. insert, update, delete, find, etc.

It is an error to call mongoc_collection_destroy() on a collection that has operations pending. It is required that you release mongoc_cursor_t structures before calling mongoc_collection_destroy().

See mongoc_collection_t.

Introduced properties

fun aggregate(pipeline: NativeBSON): nullable NativeMongoCursor

mongodb :: NativeMongoCollection :: aggregate

Wrapper for mongoc_collection_aggregate().
fun count(query: NativeBSON): Int

mongodb :: NativeMongoCollection :: count

Wrapper for mongoc_collection_count().
fun destroy

mongodb :: NativeMongoCollection :: destroy

Wrapper for mongoc_collection_destroy().
fun drop: Bool

mongodb :: NativeMongoCollection :: drop

Wrapper for mongoc_collection_drop().
fun find(query: NativeBSON, skip: Int, limit: Int): nullable NativeMongoCursor

mongodb :: NativeMongoCollection :: find

Wrapper for mongoc_collection_find().
fun insert(document: NativeBSON): Bool

mongodb :: NativeMongoCollection :: insert

Wrapper for mongoc_collection_insert().
init new(client: NativeMongoClient, db: CString, collection: CString): NativeMongoCollection

mongodb :: NativeMongoCollection :: new

Wrapper for mongoc_client_get_collection().
fun remove(selector: NativeBSON): Bool

mongodb :: NativeMongoCollection :: remove

Wrapper for mongoc_collection_remove(MONGOC_REMOVE_SINGLE_REMOVE).
fun remove_all(selector: NativeBSON): Bool

mongodb :: NativeMongoCollection :: remove_all

Wrapper for mongoc_collection_remove(MONGOC_REMOVE_NONE).
fun rename(new_database: CString, new_name: CString): Bool

mongodb :: NativeMongoCollection :: rename

Wrapper for mongoc_collection_rename().
fun save(document: NativeBSON): Bool

mongodb :: NativeMongoCollection :: save

Wrapper for mongoc_collection_save().
fun set_mongoc_error(err: BSONError)

mongodb :: NativeMongoCollection :: set_mongoc_error

Utility method to set Sys.last_mongoc_error.
fun set_mongoc_last_id(id: BSONObjectId)

mongodb :: NativeMongoCollection :: set_mongoc_last_id

Utility method to set Sys.last_mongoc_last_id.
fun stats: nullable NativeBSON

mongodb :: NativeMongoCollection :: stats

Wrapper for mongoc_collection_stats().
fun update(selector: NativeBSON, update: NativeBSON): Bool

mongodb :: NativeMongoCollection :: update

Wrapper for mongoc_collection_update(MONGOC_UPDATE_NONE).
fun update_all(selector: NativeBSON, update: NativeBSON): Bool

mongodb :: NativeMongoCollection :: update_all

Wrapper for mongoc_collection_update(MONGOC_UPDATE_MULTI_UPDATE).

Redefined properties

redef type SELF: NativeMongoCollection

mongodb $ NativeMongoCollection :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun address_is_null: Bool

core :: Pointer :: address_is_null

Is the address behind this Object at NULL?
fun aggregate(pipeline: NativeBSON): nullable NativeMongoCursor

mongodb :: NativeMongoCollection :: aggregate

Wrapper for mongoc_collection_aggregate().
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
fun count(query: NativeBSON): Int

mongodb :: NativeMongoCollection :: count

Wrapper for mongoc_collection_count().
fun destroy

mongodb :: NativeMongoCollection :: destroy

Wrapper for mongoc_collection_destroy().
fun drop: Bool

mongodb :: NativeMongoCollection :: drop

Wrapper for mongoc_collection_drop().
fun find(query: NativeBSON, skip: Int, limit: Int): nullable NativeMongoCursor

mongodb :: NativeMongoCollection :: find

Wrapper for mongoc_collection_find().
fun free

core :: Pointer :: free

Free the memory pointed by this pointer
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun insert(document: NativeBSON): Bool

mongodb :: NativeMongoCollection :: insert

Wrapper for mongoc_collection_insert().
fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
init new(client: NativeMongoClient, db: CString, collection: CString): NativeMongoCollection

mongodb :: NativeMongoCollection :: new

Wrapper for mongoc_client_get_collection().
init nul: Pointer

core :: Pointer :: nul

C NULL pointer
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
fun remove(selector: NativeBSON): Bool

mongodb :: NativeMongoCollection :: remove

Wrapper for mongoc_collection_remove(MONGOC_REMOVE_SINGLE_REMOVE).
fun remove_all(selector: NativeBSON): Bool

mongodb :: NativeMongoCollection :: remove_all

Wrapper for mongoc_collection_remove(MONGOC_REMOVE_NONE).
fun rename(new_database: CString, new_name: CString): Bool

mongodb :: NativeMongoCollection :: rename

Wrapper for mongoc_collection_rename().
fun save(document: NativeBSON): Bool

mongodb :: NativeMongoCollection :: save

Wrapper for mongoc_collection_save().
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun set_mongoc_error(err: BSONError)

mongodb :: NativeMongoCollection :: set_mongoc_error

Utility method to set Sys.last_mongoc_error.
fun set_mongoc_last_id(id: BSONObjectId)

mongodb :: NativeMongoCollection :: set_mongoc_last_id

Utility method to set Sys.last_mongoc_last_id.
fun stats: nullable NativeBSON

mongodb :: NativeMongoCollection :: stats

Wrapper for mongoc_collection_stats().
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun update(selector: NativeBSON, update: NativeBSON): Bool

mongodb :: NativeMongoCollection :: update

Wrapper for mongoc_collection_update(MONGOC_UPDATE_NONE).
fun update_all(selector: NativeBSON, update: NativeBSON): Bool

mongodb :: NativeMongoCollection :: update_all

Wrapper for mongoc_collection_update(MONGOC_UPDATE_MULTI_UPDATE).
package_diagram mongodb::NativeMongoCollection NativeMongoCollection core::Pointer Pointer mongodb::NativeMongoCollection->core::Pointer core::Object Object core::Pointer->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

extern class Pointer

core :: Pointer

Pointer classes are used to manipulate extern C structures.

Class definitions

mongodb $ NativeMongoCollection
# Wrapper for `mongoc_collection_t`.
#
# `mongoc_collection_t` provides access to a MongoDB collection.
# This handle is useful for actions for most CRUD operations,
# I.e. insert, update, delete, find, etc.
#
# It is an error to call `mongoc_collection_destroy()` on a collection that has
# operations pending.
# It is required that you release `mongoc_cursor_t` structures before calling
# `mongoc_collection_destroy()`.
#
# See [`mongoc_collection_t`](http://api.mongodb.org/c/current/mongoc_collection_t.html).
extern class NativeMongoCollection `{ mongoc_collection_t * `}

	# Wrapper for `mongoc_client_get_collection()`.
	#
	# Get a newly allocated `mongoc_collection_t` for the collection named
	# `collection` in the database named `db`.
	#
	# Collections are automatically created on the MongoDB server upon insertion
	# of the first document.
	# There is no need to create a collection manually.
	new(client: NativeMongoClient, db, collection: CString) `{
		return mongoc_client_get_collection(client, db, collection);
	`}

	# Wrapper for `mongoc_collection_insert()`.
	#
	# This function shall insert `document` into the collection.
	# If no `_id` element is found in document, then a `bson_oid_t` will be
	# generated locally and added to the document.
	#
	# You can retrieve a generated `_id` from `sys.last_mongoc_id`.
	fun insert(document: NativeBSON): Bool import set_mongoc_error, set_mongoc_last_id `{
		bson_oid_t oid;
		if(!bson_has_field(document, "_id")) {
			bson_oid_init (&oid, NULL);
			BSON_APPEND_OID (document, "_id", &oid);
			NativeMongoCollection_set_mongoc_last_id(self, &oid);
		}
		bson_error_t error;
		if(!mongoc_collection_insert(self, MONGOC_INSERT_NONE, document, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_save()`.
	#
	# This function shall save a document into the collection.
	# If the document has an `_id` field it will be updated.
	# Otherwise it will be inserted.
	#
	# You can retrieve a generated `_id` from `sys.last_mongoc_id`.
	fun save(document: NativeBSON): Bool import set_mongoc_error, set_mongoc_last_id `{
		bson_oid_t oid;
		if(!bson_has_field(document, "_id")) {
			bson_oid_init (&oid, NULL);
			BSON_APPEND_OID (document, "_id", &oid);
			NativeMongoCollection_set_mongoc_last_id(self, &oid);
		}
		bson_error_t error;
		if(!mongoc_collection_save(self, document, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_remove(MONGOC_REMOVE_SINGLE_REMOVE)`.
	#
	# This function shall remove the first document in the collection that matches
	# `selector`.
	# The bson selector is not validated, simply passed along as appropriate to the server.
	fun remove(selector: NativeBSON): Bool import set_mongoc_error `{
		bson_error_t error;
		if(!mongoc_collection_remove(self, MONGOC_REMOVE_SINGLE_REMOVE, selector, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_remove(MONGOC_REMOVE_NONE)`.
	#
	# This function shall remove documents in the collection that match `selector`.
	fun remove_all(selector: NativeBSON): Bool import set_mongoc_error `{
		bson_error_t error;
		if(!mongoc_collection_remove(self, MONGOC_REMOVE_NONE, selector, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_update(MONGOC_UPDATE_NONE)`.
	#
	# This function shall update the first document in the collection that
	# matches `selector`.
	fun update(selector, update: NativeBSON): Bool import set_mongoc_error `{
		bson_error_t error;
		if(!mongoc_collection_update(self, MONGOC_UPDATE_NONE, selector, update, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_update(MONGOC_UPDATE_MULTI_UPDATE)`.
	#
	# This function shall update documents in the collection that match `selector`.
	fun update_all(selector, update: NativeBSON): Bool import set_mongoc_error `{
		bson_error_t error;
		if(!mongoc_collection_update(self, MONGOC_UPDATE_MULTI_UPDATE, selector, update, NULL, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_count()`.
	#
	# This function shall execute a count `query` on the underlying collection.
	fun count(query: NativeBSON): Int import set_mongoc_error `{
		bson_error_t error;
		int64_t count = mongoc_collection_count(self, MONGOC_QUERY_NONE, query, 0, 0, NULL, &error);
		if(count < 0) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return -1;
		}
		return count;
	`}

	# Wrapper for `mongoc_collection_find()`.
	#
	# This function shall execute a `query` on the underlying collection.
	#
	# If no options are necessary, `query` can simply contain a query such as `{a:1}`.
	#
	# If you would like to specify options such as a sort order,
	# the query must be placed inside of `{"$query": {}}`.
	fun find(query: NativeBSON, skip, limit: Int): nullable NativeMongoCursor import
		NativeMongoCursor.as nullable, set_mongoc_error `{
		bson_error_t error;
		mongoc_cursor_t	*cursor;
		cursor = mongoc_collection_find(self, MONGOC_QUERY_NONE, skip, limit, 0, query, NULL, NULL);
		if (mongoc_cursor_error(cursor, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return null_NativeMongoCursor();
		}
		return NativeMongoCursor_as_nullable(cursor);
	`}

	# Wrapper for `mongoc_collection_aggregate()`.
	#
	# This function shall execute an aggregation `pipeline` on the underlying collection.
	#
	# The `pipeline` parameter should contain a field named `pipeline` containing
	# a BSON array of pipeline stages.
	fun aggregate(pipeline: NativeBSON): nullable NativeMongoCursor import
		NativeMongoCursor.as nullable, set_mongoc_error `{
		bson_error_t error;
		mongoc_cursor_t	*cursor;
		cursor = mongoc_collection_aggregate(self, MONGOC_QUERY_NONE, pipeline, NULL, NULL);
		if (mongoc_cursor_error(cursor, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return null_NativeMongoCursor();
		}
		return NativeMongoCursor_as_nullable(cursor);
	`}

	# Wrapper for `mongoc_collection_stats()`.
	#
	# This function is a helper to retrieve statistics about the collection.
	fun stats: nullable NativeBSON import set_mongoc_error, NativeBSON.as nullable `{
		bson_error_t error;
		bson_t *reply = bson_new();
		if(!mongoc_collection_stats(self, NULL, reply, &error)){
			NativeMongoCollection_set_mongoc_error(self, &error);
			return null_NativeBSON();
		}
		return NativeBSON_as_nullable(reply);
	`}

	# Wrapper for `mongoc_collection_drop()`.
	#
	# This function requests that the `collection` be dropped,
	# including all indexes associated with the collection.
	fun drop: Bool import set_mongoc_error `{
		bson_error_t error;
		if(!mongoc_collection_drop(self, &error)) {
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_rename()`.
	#
	# This function is a helper to rename an existing collection on a MongoDB server.
	# The name of the collection will also be updated internally so it is safe
	# to continue using this collection after the rename.
	# Additional operations will occur on renamed collection.
	fun rename(new_database, new_name: CString): Bool `{
		bson_error_t error;
		if(!mongoc_collection_rename(self, new_database, new_name, false, &error)){
			NativeMongoCollection_set_mongoc_error(self, &error);
			return false;
		}
		return true;
	`}

	# Wrapper for `mongoc_collection_destroy()`.
	#
	# This instance should not be used beyond this point!
	fun destroy `{ mongoc_collection_destroy(self); `}

	# Utility method to set `Sys.last_mongoc_last_id`.
	fun set_mongoc_last_id(id: BSONObjectId) do sys.last_mongoc_id = id

	# Utility method to set `Sys.last_mongoc_error`.
	fun set_mongoc_error(err: BSONError) do sys.last_mongoc_error = err
end
lib/mongodb/native_mongodb.nit:293,1--516,3