| Safe Haskell | None |
|---|
Database.CouchDB.Enumerator
Contents
Description
With the advent of conduits, you are strongly encouraged to use couchdb-conduit http://hackage.haskell.org/package/couchdb-conduit instead of this package. It exports almost the same interface but uses conduits instead of enumerator.
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
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
-- Make database if not present
couchPutDb ""
-- 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) ()
-- .. with restrictions and extracting view value
run_ $ couchView "testdesign/_view/myview"
[(fromString "key", Just $ fromString "10")] $= extractViewValue $$
EL.foldM (\_ o -> liftIO $ BL.putStrLn $ encode $ Object o) ()
-- .. and in strict manner
v1 <- couchView "testdesign/_view/myview" [] $= extractViewValue
EL.consume
print v1
-- Delete the objects
couchDelete "doc1" rev3
couchDelete "doc2" rev2
-- Delete test database
couchDeleteDb ""
- data CouchConnection = CouchConnection {}
- runCouch :: (MonadIO m, MonadBaseControl IO m) => String -> Int -> String -> ReaderT CouchConnection m a -> m a
- withCouchConnection :: MonadBaseControl IO m => String -> Int -> String -> (CouchConnection -> m a) -> m a
- data CouchError = CouchError (Maybe Int) String
- class (MonadIO m, MonadBaseControl IO m) => MonadCouch m where
- couchPutDb :: MonadCouch m => Path -> m ()
- couchDeleteDb :: MonadCouch m => Path -> m ()
- type Path = String
- type Revision = Text
- couchRev :: MonadCouch m => Path -> m Revision
- couchGet :: MonadCouch m => Path -> Query -> m Object
- couchPut :: (MonadCouch m, ToJSON a) => Path -> Query -> a -> m Revision
- couchPutRev :: (MonadCouch m, ToJSON a) => Path -> Revision -> Query -> a -> m Revision
- couchPut_ :: (MonadCouch m, ToJSON a) => Path -> Query -> a -> m ()
- couchDelete :: MonadCouch m => Path -> Revision -> m ()
- couchView :: MonadCouch m => Path -> Query -> Enumerator Object m a
- extractViewValue :: Monad m => Enumeratee Object Object m a
- couch :: MonadCouch m => Method -> Path -> Query -> Iteratee ByteString m a -> RequestBody m -> Iteratee ByteString m a
- couch' :: MonadCouch m => Method -> Path -> RequestHeaders -> Query -> (ResponseHeaders -> Iteratee ByteString m a) -> RequestBody m -> Iteratee ByteString m a
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.
To access more than one database, the dbname entry can be set to the empty string.
Constructors
| CouchConnection | |
Instances
| (MonadIO m, MonadBaseControl IO m) => MonadCouch (ReaderT CouchConnection m) |
Arguments
| :: (MonadIO m, MonadBaseControl IO m) | |
| => String | Host |
| -> Int | Port |
| -> String | Database name. Just set empty if you need access to many DBs |
| -> 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
Arguments
| :: MonadBaseControl IO m | |
| => String | Host |
| -> Int | Port |
| -> String | Database name. Just set empty if you need access to many DBs |
| -> (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 |
Instances
class (MonadIO m, MonadBaseControl IO m) => MonadCouch m whereSource
A monad which allows access to the connection.
Methods
Instances
| (MonadIO m, MonadBaseControl IO m) => MonadCouch (ReaderT CouchConnection m) |
Couch DB database API
Arguments
| :: MonadCouch m | |
| => Path | If you passed a database name to |
| -> m () |
Create CouchDB database regardless of presence. Roughly equivalent to
couchPut_ "" [] $ object []
but catches CouchError 412.
Arguments
| :: MonadCouch m | |
| => Path | If you passed a database name to |
| -> m () |
Delete a database.
Couch DB documents API
couchRev :: MonadCouch m => Path -> m RevisionSource
Get Revision of a document.
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.
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.
Arguments
| :: (MonadCouch m, ToJSON a) | |
| => Path | the dbname is prepended to this string to form the full path. |
| -> Revision | Document revision. For new docs provide empty string. |
| -> Query | Query arguments. |
| -> a | The object to store. |
| -> m Revision |
Put an object in Couch DB with revision, returning the new Revision.
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.
Arguments
| :: MonadCouch m | |
| => Path | the dbname is prepended to this string to form the full path. |
| -> Revision | Document revision. |
| -> m () |
Delete the given revision of the object.
Couch DB views API
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":"64ACF01B05F53...", "key":null, "value": { some object } }
and this enumeratee will extract {some object}
Low-level API
Arguments
| :: MonadCouch m | |
| => Method | Method |
| -> Path | The dbname from the connection is prepended to this path. Just set empty if you need access to many DBs. |
| -> Query | Query arguments |
| -> Iteratee ByteString m a | Iteratee to process the response if no error occurs. |
| -> RequestBody m | Body |
| -> Iteratee ByteString m a |
Simplified version of couch'.
Response headers are ignored, and the response status is only used to
detect for an error, in which case a CouchError is sent down the
Iteratee.
Arguments
| :: MonadCouch m | |
| => Method | Method |
| -> Path | The dbname from the connection is prepended to this path. Just set empty if you need access to many DBs. |
| -> RequestHeaders | Headers |
| -> Query | Query arguments |
| -> (ResponseHeaders -> Iteratee ByteString m a) | Function what returns 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.
If CouchDB returns an error, the iteratee passed to this function is not
called and instead a CouchError is sent out the Iteratee returned from
this function.
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.