couchdb-enumerator-0.2.0: Couch DB client library using http-enumerator and aeson

Database.CouchDB.Enumerator

Contents

Description

This module is a very thin wrapper around Network.HTTP.Enumerator using the aeson package to parse and encode JSON. The Couch DB HTTP API is the best place to learn about how to use this library. http://wiki.apache.org/couchdb/Complete_HTTP_API_Reference

 {-# LANGUAGE OverloadedStrings #-}
 import Control.Monad.IO.Class (liftIO)
 import Data.Aeson
 import qualified Data.ByteString.Lazy as BL
 import Data.ByteString.UTF8 (fromString)
 import Data.Enumerator (($$), run_)
 import qualified Data.Enumerator.List as EL
 import Database.CouchDB.Enumerator

 testCouch :: IO ()
 testCouch = withCouchConnection "localhost" 5984 "test" $ runCouchT $ do
    
    -- Insert some documents.   Note that the dbname passed to withCouchConnection
    -- is prepended to the given path, so this is a put to
    -- http://localhost:5983/test/doc1
    rev1 <- couchPut "doc1" [] $ object [ "foo" .= (3 :: Int), "bar" .= ("abc" :: String) ]
    rev2 <- couchPut "doc2" [] $ object [ "foo" .= (7 :: Int), "baz" .= (145 :: Int) ]

    -- Load the document and print it out
    couchGet "doc1" [] >>= liftIO . BL.putStrLn . encode . Object

    -- Overwite the document.  We supply the revision, otherwise Couch DB would give an error.
    -- (The revision could also have been passed in the query arguments.)
    rev3 <- couchPut "doc1" [] $ object [ "foo" .= (10 :: Int)
                                        , "bar" .= ("def" :: String)
                                        , "_rev" .= rev1 
                                        ]

    -- Create a view
    couchPut_ "_design/testdesign" [] $ 
        object [ "language" .= ("javascript" :: String)
               , "views"    .= object [ "myview" .= object [ "map" .=
                    ("function(doc) { emit(doc.foo, doc); }" :: String)
                    ]]
               ]

    -- Read from the view using couchGet and print it out.
    couchGet "_design/testdesign/_view/myview" [] >>= liftIO . BL.putStrLn . encode . Object
    couchGet "_design/testdesign/_view/myview" [(fromString "key", Just $ fromString "10")]
            >>= liftIO . BL.putStrLn . encode . Object

    -- Read the view using couchView and print it out.
    run_ $ couchView "testdesign/_view/myview" [] $$
        EL.foldM (\_ o -> liftIO $ BL.putStrLn $ encode $ Object o) ()
    run_ $ couchView "testdesign/_view/myview" [(fromString "key", Just $ fromString "10")] $$
        EL.foldM (\_ o -> liftIO $ BL.putStrLn $ encode $ Object o) ()

    -- Delete the objects
    couchDelete "doc1" rev3
    couchDelete "doc2" rev2

Synopsis

Couch DB Connection

data CouchConnection Source

Represents a (pooled) connection to a single Couch DB Dabase.

Constructors

CouchConnection 

withCouchConnectionSource

Arguments

:: MonadControlIO m 
=> String

host

-> Int

port

-> String

database name

-> (CouchConnection -> m a)

function to run

-> m a 

Connect to a CouchDB database, call the supplied function, and then close the connection.

data CouchError Source

A Couch DB Error. If the error comes from http, the http status code is also given. Non-http errors include things like errors parsing the response.

Constructors

CouchError (Maybe Int) String 

class MonadIO m => CouchMonad m whereSource

A monad which allows access to the couch connection.

Instances

Accessing Couch DB

type Path = StringSource

A path to a Couch DB Object.

type Revision = TextSource

Represents a revision of a Couch DB Document.

couchGetSource

Arguments

:: CouchMonad m 
=> Path

the dbname is prepended to this string to form the full path.

-> Query

Query arguments.

-> m Object 

Load a single object from couch DB.

couchPutSource

Arguments

:: (CouchMonad m, ToJSON a) 
=> Path

the dbname is prepended to this string to form the full path.

-> Query

Query arguments.

-> a

The object to store.

-> m Revision 

Put an object in Couch DB, returning the new Revision.

couchPut_Source

Arguments

:: (CouchMonad m, ToJSON a) 
=> Path

the dbname is prepended to this string to form the full path.

-> Query

Query arguments.

-> a

The object to store.

-> m () 

A version of couchPut which ignores the return value. This is slightly faster than _ <- couchPut ... since the JSON parser is not run.

couchDeleteSource

Arguments

:: CouchMonad m 
=> Path

the dbname is prepended to this string to form the full path.

-> Revision 
-> m () 

Delete the given revision of the object.

couchViewSource

Arguments

:: CouchMonad m 
=> Path

/dbname/_design/ is prepended to the given path

-> Query

Query arguments.

-> Enumerator Object m a 

Load from a Couch DB View.

While you can use couchGet on a view object, this function combines the incredible power of http-enumerator and attoparsec to allow you to process objects in constant space. As data is read from the network, it is fed into attoparsec. When attoparsec completes parsing an object it is sent out the enumerator.

The objects enumerated are the entries in the "rows" property of the view result, which means they are not directly the objects you put into the database. See http://wiki.apache.org/couchdb/HTTP_view_API for more information. The objects inserted into the database are available in the "value" entry, and can be extracted with the extractViewValue enumeratee, for example:

  couchView "mydesigndoc/_view/myview" [(fromString "key", Just $ fromString "3")] $= extractViewValue

extractViewValue :: Monad m => Enumeratee Object Object m aSource

An enumeratee to extract the "value" member of JSON objects.

This is useful to extract the object from the data returned from a view. For example, Couch DB will return objects that look like the following:

    { "id":"64ACF01B05F53ACFEC48C062A5D01D89", "key":null, "value": { some object } }

and this enumeratee will extract {some object}

couchSource

Arguments

:: CouchMonad m 
=> Method

Method

-> Path

The dbname from the connection is prepended to this path.

-> Query

Query arguments

-> Iteratee ByteString m a

Iteratee to process the response

-> RequestBody m

body

-> Iteratee ByteString m a 

The most general method of accessing CouchDB. This is a very thin wrapper around http. Most of the time you should use one of the other access functions, but this function is needed for example to write and read attachments that are not in JSON format.

A ReaderT CouchMonad

newtype CouchT m a Source

ReaderT implementation of CouchMonad.

Constructors

CouchT (ReaderT CouchConnection m a) 

runCouchT :: Monad m => CouchT m a -> CouchConnection -> m aSource

Run a Couch DB backend.