Safe Haskell | None |
---|
CouchDB
To work with concrete objects, use the following modules:
- Database.CouchDB.Conduit.DB Database
- Database.CouchDB.Conduit.View Views
- Database.CouchDB.Conduit.LowLevel Low-level methods
For complete documentation about The Couch DB HTTP API see http://wiki.apache.org/couchdb/Complete_HTTP_API_Reference
- type Path = ByteString
- type Revision = ByteString
- mkPath :: [Path] -> Path
- data CouchConnection
- def :: Default a => a
- couchHost :: CouchConnection -> ByteString
- couchPort :: CouchConnection -> Int
- couchLogin :: CouchConnection -> ByteString
- couchPass :: CouchConnection -> ByteString
- couchPrefix :: CouchConnection -> ByteString
- class (MonadResource m, MonadBaseControl IO m) => MonadCouch m where
- couchConnection :: m (Manager, CouchConnection)
- data CouchError
- runCouch :: MonadResourceBase m => CouchConnection -> ReaderT (Manager, CouchConnection) (ResourceT m) a -> m a
- withCouchConnection :: (MonadResource m, MonadBaseControl IO m) => Manager -> CouchConnection -> ((Manager, CouchConnection) -> m a) -> m a
- couchRev :: MonadCouch m => Path -> Path -> m Revision
- couchRev' :: MonadCouch m => Path -> Path -> m Revision
- couchDelete :: MonadCouch m => Path -> Path -> Revision -> m ()
Document paths and revisions
type Path = ByteStringSource
Represents a path or path fragment.
As a rule, full path to document in CouchDB is just URL path. But there is one subtlety. For example, document ids can contain slashes. But, to work with such objects, path fragments must be escaped.
database/doc%2Fname
But, fo non-document items such as views, attachments e.t.c., slashes between path fragments must not be escaped. While slashes in path fragments must be escaped.
database/_design/my%2Fdesign/_view/my%2Fview
Except low-level functions, couchdb-conduit
escapes all segments in paths.
type Revision = ByteStringSource
Represents a revision of a CouchDB Document.
Make correct path and escape fragments. Filter empty fragments.
mkPath ["db", "", "doc/with/slashes"] /db/doc%2Fwith%2Fslashes
CouchDB Connection
data CouchConnection Source
Represents a single connection to CouchDB server. The constructor for this
data type is not exposed. Instead, you should use either the def
method
to retrieve a default instance.
Default CouchConnection | |
(MonadResource (ReaderT (Manager, CouchConnection) m), MonadBaseControl IO (ReaderT (Manager, CouchConnection) m), MonadResource m, MonadBaseControl IO m) => MonadCouch (ReaderT (Manager, CouchConnection) m) |
couchHost :: CouchConnection -> ByteStringSource
Hostname. Default value is "localhost"
couchPort :: CouchConnection -> IntSource
Port. 5984 by default.
couchLogin :: CouchConnection -> ByteStringSource
CouchDB login. By default is empty
.
couchPass :: CouchConnection -> ByteStringSource
CouchDB password. By default is empty
.
couchPrefix :: CouchConnection -> ByteStringSource
CouchDB database prefix. It will prepended to first fragment of request path. Must be fully valid DB name fragment.
Runtime enviroment and errors
class (MonadResource m, MonadBaseControl IO m) => MonadCouch m whereSource
A monad which allows access to the connection.
All functions to access CouchDB require a MonadCouch
instance to
access the connection information. ReaderT
is an instance of
MonadCouch
, and runCouch runs a sequence of database actions using
ReaderT
and ResourceT
.
If your db code is part of a larger monad, it makes sense to just make the
larger monad an instance of MonadCouch
and skip the intermediate ReaderT,
since then performance is improved by eliminating one monad from the final
transformer stack.
(MonadResource (ReaderT (Manager, CouchConnection) m), MonadBaseControl IO (ReaderT (Manager, CouchConnection) m), MonadResource m, MonadBaseControl IO m) => MonadCouch (ReaderT (Manager, CouchConnection) m) |
data CouchError Source
A CouchDB Error.
CouchHttpError Int ByteString | Error comes from http. |
CouchInternalError ByteString | Non-http errors include things like errors parsing the response. |
NotModified | Is not an error actually. It is thrown when CouchDB returns
|
:: MonadResourceBase m | |
=> CouchConnection | Couch connection |
-> ReaderT (Manager, CouchConnection) (ResourceT m) a | Actions |
-> m a |
Connect to a CouchDB server, run a sequence of CouchDB actions, and then
close the connection.. This function is a combination of withManager
,
withCouchConnection
, runReaderT
and runResourceT
.
If you create your own instance of MonadCouch
or use connection pool,
use withCouchConnection
.
:: (MonadResource m, MonadBaseControl IO m) | |
=> Manager | Connection manager |
-> CouchConnection | Couch connection |
-> ((Manager, CouchConnection) -> m a) | Actions |
-> m a |
Run a sequence of CouchDB actions with provided Manager
and
CouchConnection
.
withCouchConnection manager def {couchDB = "db"} . runReaderT . runResourceT . lift $ do ... -- actions
Documents
:: MonadCouch m | |
=> Path | Database. |
-> Path | Document path. |
-> m Revision |
Get Revision of a document.
:: MonadCouch m | |
=> Path | Database. |
-> Path | Document path. |
-> m Revision |
Brain-free version of couchRev
. If document absent,
just return empty ByteString.
:: MonadCouch m | |
=> Path | Database. |
-> Path | Document path. |
-> Revision | Revision |
-> m () |
Delete the given revision of the object.