couchdb-enumerator-0.3.4: 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 = runCouch "localhost" 5984 "test" $ 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:5984/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 connection to a single Couch DB Database.

A connection contains a Manager and reuses it for multiple requests, which means a single open HTTP connection to CouchDB will be kept around until the manager is closed (http-enumerator will create more connections if needed, it just keeps only one and closes the rest.) See the Pool section for more information.

Constructors

CouchConnection 

runCouchSource

Arguments

:: (MonadIO m, MonadBaseControl IO m) 
=> String

host

-> Int

port

-> String

database name

-> ReaderT CouchConnection m a

CouchDB actions

-> m a 

Run a sequence of CouchDB actions.

The functions below 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. See the top of this page for an example using runCouch.

The main reason to not use runCouch is to obtain more control over connection pooling. Also, 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.

This function is a combination of withCouchConnection and runReaderT

withCouchConnectionSource

Arguments

:: MonadBaseControl IO 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.

If you create your own instance of MonadCouch instead of using runCouch, this function will help you create the CouchConnection. On the other hand, if you want to implement connection pooling, you will not be able to use withCouchConnection and must create the connection yourself.

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 => MonadCouch m whereSource

A monad which allows access to the connection.

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

:: MonadCouch 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

:: (MonadCouch 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

:: (MonadCouch 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

:: MonadCouch 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

:: MonadCouch 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

:: MonadCouch 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 if no error occurs.

-> 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.

Connection Pooling

The Manager stored in the CouchConnection maintains a pool of open connections in an IORef, but keeps a maximum of one open connection per (host,port) pair. Also, each time runCouch or withCouchConnection is called, a new manager (and thus new connections) is created and destroyed.

For more precise control over pooling, use the http://hackage.haskell.org/package/resource-pool or http://hackage.haskell.org/package/pool packages combined with the newManager and closeManager functions.

For example, the following code using the resource-pool package runs a ReaderT CouchConnection m action using a HTTP connection from a pool.

 runPooledCouch :: MonadCatchIO m
                => Pool Manager -> String -> Int -> String -> ReaderT CouchConnection m a -> m a
 runPooledCouch p host port dbname c = withResource p $ \m -> do
    runReaderT c $ CouchConnection (BU8.fromString host) port m dbname

Yesod Integration

Integrating couchdb-enumerator with yesod looks something the way the scaffold sets up the YesodPersist instance.

 data MyFoundation = MyFoundation 
     { ... (normal yesod stuff in the foundation type)
     , connPool     :: Data.Pool.Pool H.Manager
     , dbLocation   :: B.ByteString
     , databaseName :: String
     }

 newtype CouchDBPersist m a = CouchDBPersist { unCouchDBPersist :: ReaderT CouchConnection m a }
     deriving (Monad, MonadIO, MonadTrans, Functor, Applicative, MonadTransControl,
               MonadBaseControl, MonadPlus, MonadCouch)

 instance YesodPersist MyFoundation where
     type YesodPersistBackend = CouchDBPersist
     runDB r = do pool <- connPool <$> getYesod
                  loc <- dbLocation <$> getYesod
                  db <- databaseName <$> getYesod
                  Data.Pool.withPool' pool $ \m ->
                      runReaderT (unCouchDBPersist r) $ CouchConnection loc 5984 m db

Then you can write handler code as follows:

 getFooR :: PersonID -> Handler RepPlain
 getFooR p = do
    person <- runDB $ couchGet p []
    return $ RepPlain $ toContent $ Aeson.encode $ maybe Aeson.null person

Alternatively, you don't need to make your Foundation an instance of YesodPersist, you could supply your own runCouchDB function which is just a version of runDB specialized to your foundation and just use that from the handlers.