persistent-mongoDB-2.5.0.1: Backend for the persistent library using mongoDB.

Safe HaskellNone
LanguageHaskell98

Database.Persist.MongoDB

Contents

Description

Use persistent-mongodb the same way you would use other persistent libraries and refer to the general persistent documentation. There are some new MongoDB specific filters under the filters section. These help extend your query into a nested document.

However, at some point you will find the normal Persistent APIs lacking. and want lower level-level MongoDB access. There are functions available to make working with the raw driver easier: they are under the Entity conversion section. You should still use the same connection pool that you are using for Persistent.

MongoDB is a schema-less database. The MongoDB Persistent backend does not help perform migrations. Unlike SQL backends, uniqueness constraints cannot be created for you. You must place a unique index on unique fields.

Synopsis

Entity conversion

docToEntityEither :: forall record. PersistEntity record => Document -> Either Text (Entity record) Source #

docToEntityThrow :: forall m record. (MonadIO m, PersistEntity record, PersistEntityBackend record ~ MongoContext) => Document -> m (Entity record) Source #

entityToDocument :: (PersistEntity record, PersistEntityBackend record ~ MongoContext) => record -> Document Source #

Deprecated: use recordToDocument

recordToDocument :: (PersistEntity record, PersistEntityBackend record ~ MongoContext) => record -> Document Source #

convert a PersistEntity into document fields. unlike toInsertDoc, nulls are included.

toInsertDoc :: forall record. (PersistEntity record, PersistEntityBackend record ~ MongoContext) => record -> Document Source #

convert a PersistEntity into document fields. for inserts only: nulls are ignored so they will be unset in the document. entityToDocument includes nulls

entityToInsertDoc :: forall record. (PersistEntity record, PersistEntityBackend record ~ MongoContext) => Entity record -> Document Source #

toUniquesDoc :: forall record. PersistEntity record => Unique record -> [Field] Source #

convert a unique key into a MongoDB document

MongoDB specific queries

(->.) :: forall record emb typ. PersistEntity emb => EntityField record [emb] -> EntityField emb typ -> NestedField record typ infixr 6 Source #

Point to an array field with an embedded object and give a deeper query into the embedded object. Use with nestEq.

(~>.) :: forall record typ emb. PersistEntity emb => EntityField record [emb] -> NestedField emb typ -> NestedField record typ infixr 5 Source #

Point to an array field with an embedded object and give a deeper query into the embedded object. This level of nesting is not the final level. Use ->. or &->. to point to the final level.

(?&->.) :: forall record typ nest. PersistEntity nest => EntityField record (Maybe nest) -> EntityField nest typ -> NestedField record typ infixr 6 Source #

Same as &->., but Works against a Maybe type

(?&~>.) :: forall val nes nes1. PersistEntity nes1 => EntityField val (Maybe nes1) -> NestedField nes1 nes -> NestedField val nes infixr 5 Source #

Same as &~>., but works against a Maybe type

(&->.) :: forall record typ nest. PersistEntity nest => EntityField record nest -> EntityField nest typ -> NestedField record typ infixr 6 Source #

Point to a nested field to query. This field is not an array type. Use with nestEq.

(&~>.) :: forall val nes nes1. PersistEntity nes1 => EntityField val nes1 -> NestedField nes1 nes -> NestedField val nes infixr 5 Source #

Point to a nested field to query. This field is not an array type. This level of nesting is not the final level. Use ->. or &>. to point to the final level.

Filters

You can find example usage for all of Persistent in our test cases: https://github.com/yesodweb/persistent/blob/master/persistent-test/EmbedTest.hs#L144

These filters create a query that reaches deeper into a document with nested fields.

nestEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

nestNe :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

nestGe :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

nestLe :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

nestIn :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

nestNotIn :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Filter record infixr 4 Source #

The normal Persistent equality test ==. is not generic enough. Instead use this with the drill-down arrow operaters such as ->.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({"object.field": item})

anyEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> typ -> Filter record infixr 4 Source #

Like '(==.)' but for an embedded list. Checks to see if the list contains an item.

In Haskell we need different equality functions for embedded fields that are lists or non-lists to keep things type-safe.

using this as the only query filter is similar to the following in the mongoDB shell

db.Collection.find({arrayField: arrayItem})

nestAnyEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record [typ] -> typ -> Filter record infixr 4 Source #

Like nestEq, but for an embedded list. Checks to see if the nested list contains an item.

nestBsonEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> Value -> Filter record infixr 4 Source #

same as nestEq, but give a BSON Value

anyBsonEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> Value -> Filter record infixr 4 Source #

same as anyEq, but give a BSON Value

multiBsonEq :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> Value -> Filter record infixr 4 Source #

Deprecated: Please use anyBsonEq instead

inList :: PersistField typ => EntityField v [typ] -> [typ] -> Filter v infix 4 Source #

Intersection of lists: if any value in the field is found in the list.

ninList :: PersistField typ => EntityField v [typ] -> [typ] -> Filter v infix 4 Source #

No intersection of lists: if no value in the field is found in the list.

(=~.) :: forall record searchable. (MongoRegexSearchable searchable, PersistEntity record, PersistEntityBackend record ~ MongoContext) => EntityField record searchable -> MongoRegex -> Filter record infixr 4 Source #

Filter using a Regular expression.

data NestedField record typ Source #

Constructors

PersistEntity emb => (EntityField record [emb]) `LastEmbFld` (EntityField emb typ) 
PersistEntity emb => (EntityField record [emb]) `MidEmbFld` (NestedField emb typ) 
PersistEntity nest => (EntityField record nest) `MidNestFlds` (NestedField nest typ) 
PersistEntity nest => (EntityField record (Maybe nest)) `MidNestFldsNullable` (NestedField nest typ) 
PersistEntity nest => (EntityField record nest) `LastNestFld` (EntityField nest typ) 
PersistEntity nest => (EntityField record (Maybe nest)) `LastNestFldNullable` (EntityField nest typ) 

class PersistField typ => MongoRegexSearchable typ Source #

Mark the subset of PersistFields that can be searched by a mongoDB regex Anything stored as PersistText or an array of PersistText would be valid

type MongoRegex = (Text, Text) Source #

A MongoRegex represents a Regular expression. It is a tuple of the expression and the options for the regular expression, respectively Options are listed here: http://docs.mongodb.org/manual/reference/operator/query/regex/ If you use the same options you may want to define a helper such as r t = (t, "ims")

Updates

nestSet :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Update record infixr 4 Source #

nestInc :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Update record Source #

nestDec :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Update record Source #

nestMul :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => NestedField record typ -> typ -> Update record Source #

push :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> typ -> Update record infixr 4 Source #

pull :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> typ -> Update record infixr 4 Source #

pullAll :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> [typ] -> Update record infixr 4 Source #

addToSet :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => EntityField record [typ] -> typ -> Update record infixr 4 Source #

eachOp :: forall record typ. (PersistField typ, PersistEntityBackend record ~ MongoContext) => (EntityField record [typ] -> typ -> Update record) -> EntityField record [typ] -> [typ] -> Update record Source #

equivalent to $each

eachOp push field []

eachOp pull will get translated to $pullAll

Key conversion helpers

recordTypeFromKey :: Key record -> record Source #

readMayMongoKey :: Text -> Maybe (BackendKey MongoContext) Source #

Convert a Text to a Key

PersistField conversion

fieldName :: forall record typ. PersistEntity record => EntityField record typ -> Label Source #

using connections

createMongoDBPool Source #

Arguments

:: (MonadIO m, Applicative m) 
=> Database 
-> HostName 
-> PortID 
-> Maybe MongoAuth 
-> Int

pool size (number of stripes)

-> Int

stripe size (number of connections per stripe)

-> NominalDiffTime

time a connection is left idle before closing

-> m ConnectionPool 

runMongoDBPoolDef :: (MonadIO m, MonadBaseControl IO m) => Action m a -> ConnectionPool -> m a Source #

use default AccessMode

Connection configuration

applyDockerEnv :: MongoConf -> IO MongoConf Source #

docker integration: change the host to the mongodb link

using raw MongoDB pipes

createMongoDBPipePool Source #

Arguments

:: (MonadIO m, Applicative m) 
=> HostName 
-> PortID 
-> Int

pool size (number of stripes)

-> Int

stripe size (number of connections per stripe)

-> NominalDiffTime

time a connection is left idle before closing

-> m PipePool 

A pool of plain MongoDB pipes. The database parameter has not yet been applied yet. This is useful for switching between databases (on the same host and port) Unlike the normal pool, no authentication is available

network type

type HostName = String #

Either a host name e.g., "haskell.org" or a numeric host address string consisting of a dotted decimal IPv4 address or an IPv6 address e.g., "192.168.0.1".

data PortID :: * #

Instances

Eq PortID 

Methods

(==) :: PortID -> PortID -> Bool #

(/=) :: PortID -> PortID -> Bool #

Show PortID 

MongoDB driver types

type Database = Text #

type Action = ReaderT * MongoContext #

A monad on top of m (which must be a MonadIO) that may access the database and may fail with a DB Failure

data AccessMode :: * #

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.

(=:) :: Val v => Label -> v -> Field infix 0 #

Field with given label and typed value

data ObjectId :: * #

A BSON ObjectID is a 12-byte value consisting of a 4-byte timestamp (seconds since epoch), a 3-byte machine id, a 2-byte process id, and a 3-byte counter. Note that the timestamp and counter fields must be stored big endian unlike the rest of BSON. This is because they are compared byte-by-byte and we want to ensure a mostly increasing order.

Database.Persist

Orphan instances

Val PersistValue Source # 
Serialize ObjectId Source # 
PersistFieldSql ObjectId Source # 
PersistUniqueRead MongoContext Source # 

Methods

getBy :: (MonadIO m, PersistRecordBackend record MongoContext) => Unique record -> ReaderT * MongoContext m (Maybe (Entity record)) #

PersistUniqueWrite MongoContext Source # 

Methods

deleteBy :: (MonadIO m, PersistRecordBackend record MongoContext) => Unique record -> ReaderT * MongoContext m () #

insertUnique :: (MonadIO m, PersistRecordBackend record MongoContext) => record -> ReaderT * MongoContext m (Maybe (Key record)) #

upsert :: (MonadIO m, PersistRecordBackend record MongoContext) => record -> [Update record] -> ReaderT * MongoContext m (Entity record) #

upsertBy :: (MonadIO m, PersistRecordBackend record MongoContext) => Unique record -> record -> [Update record] -> ReaderT * MongoContext m (Entity record) #

PersistQueryRead MongoContext Source # 

Methods

selectSourceRes :: (PersistRecordBackend record MongoContext, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT * MongoContext m1 (Acquire (Source m2 (Entity record))) #

selectFirst :: (MonadIO m, PersistRecordBackend record MongoContext) => [Filter record] -> [SelectOpt record] -> ReaderT * MongoContext m (Maybe (Entity record)) #

selectKeysRes :: (MonadIO m1, MonadIO m2, PersistRecordBackend record MongoContext) => [Filter record] -> [SelectOpt record] -> ReaderT * MongoContext m1 (Acquire (Source m2 (Key record))) #

count :: (MonadIO m, PersistRecordBackend record MongoContext) => [Filter record] -> ReaderT * MongoContext m Int #

PersistQueryWrite MongoContext Source # 
HasPersistBackend MongoContext Source # 
PersistCore MongoContext Source #

older versions versions of haddock (like that on hackage) do not show that this defines BackendKey DB.MongoContext = MongoKey { unMongoKey :: DB.ObjectId }

Associated Types

data BackendKey MongoContext :: * #

PersistStoreRead MongoContext Source # 

Methods

get :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> ReaderT * MongoContext m (Maybe record) #

PersistStoreWrite MongoContext Source # 

Methods

insert :: (MonadIO m, PersistRecordBackend record MongoContext) => record -> ReaderT * MongoContext m (Key record) #

insert_ :: (MonadIO m, PersistRecordBackend record MongoContext) => record -> ReaderT * MongoContext m () #

insertMany :: (MonadIO m, PersistRecordBackend record MongoContext) => [record] -> ReaderT * MongoContext m [Key record] #

insertMany_ :: (MonadIO m, PersistRecordBackend record MongoContext) => [record] -> ReaderT * MongoContext m () #

insertEntityMany :: (MonadIO m, PersistRecordBackend record MongoContext) => [Entity record] -> ReaderT * MongoContext m () #

insertKey :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> record -> ReaderT * MongoContext m () #

repsert :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> record -> ReaderT * MongoContext m () #

replace :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> record -> ReaderT * MongoContext m () #

delete :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> ReaderT * MongoContext m () #

update :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> [Update record] -> ReaderT * MongoContext m () #

updateGet :: (MonadIO m, PersistRecordBackend record MongoContext) => Key record -> [Update record] -> ReaderT * MongoContext m record #

PersistField ObjectId Source # 
Eq (BackendKey MongoContext) Source # 
Ord (BackendKey MongoContext) Source # 
Read (BackendKey MongoContext) Source # 
Show (BackendKey MongoContext) Source # 
FromJSON (BackendKey MongoContext) Source # 
ToJSON (BackendKey MongoContext) Source #

It would make sense to define the instance for ObjectId and then use newtype deriving however, that would create an orphan instance

ToHttpApiData (BackendKey MongoContext) Source # 
FromHttpApiData (BackendKey MongoContext) Source # 
PathPiece (BackendKey MongoContext) Source #

ToPathPiece is used to convert a key to/from text

PersistFieldSql (BackendKey MongoContext) Source # 
PersistField (BackendKey MongoContext) Source #