{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables #-} {- | 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. > {-# 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 > -- 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 "" -} module Database.CouchDB.Enumerator( -- * Couch DB Connection CouchConnection(..) , runCouch , withCouchConnection , CouchError(..) , MonadCouch(..) -- * Couch DB database API , couchPutDb , couchDeleteDb -- * Couch DB documents API , Path , Revision , couchRev , couchGet , couchPut , couchPutRev , couchPut_ , couchDelete -- * Couch DB views API , couchView , extractViewValue -- * Low-level API , couch , couch' -- * Connection Pooling -- $pool -- * Yesod Integration -- $yesod ) where import Prelude hiding (catch) import Control.Applicative import Control.Exception (Exception, throw, bracket) import Control.Exception.Lifted (catch) import Control.Monad.IO.Class (MonadIO, liftIO) import Control.Monad.Trans.Class (MonadTrans, lift) import Control.Monad.Trans.Control (MonadBaseControl, liftBaseOp) import Control.Monad.Trans.Reader (ReaderT, ask, runReaderT) import Data.Maybe (fromJust) import qualified Data.Aeson as A --import qualified Data.Aeson.Encode as AE import Data.Attoparsec import Data.Attoparsec.Enumerator (iterParser) import qualified Data.ByteString as B import qualified Data.ByteString.UTF8 as BU8 import Data.Enumerator hiding (map) import qualified Data.HashMap.Lazy as M import qualified Data.Text as T import qualified Data.Text.Encoding as TE import Data.Typeable (Typeable) import qualified Network.HTTP.Enumerator as H import qualified Network.HTTP.Types as HT -- | Represents a connection to a single Couch DB Database. -- -- A connection contains a 'H.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. data CouchConnection = CouchConnection { host :: B.ByteString , port :: Int , manager :: H.Manager , dbname :: String } -- | 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. withCouchConnection :: (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 withCouchConnection h p db f = liftBaseOp (bracket H.newManager H.closeManager) go where go m = f $ CouchConnection (BU8.fromString h) p m db -- | 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. data CouchError = CouchError (Maybe Int) String deriving (Show,Typeable) instance Exception CouchError -- | A monad which allows access to the connection. class (MonadIO m, MonadBaseControl IO m) => MonadCouch m where couchConnection :: m CouchConnection instance (MonadIO m, MonadBaseControl IO m) => MonadCouch (ReaderT CouchConnection m) where couchConnection = ask -- | 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' runCouch :: (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 runCouch h p d = withCouchConnection h p d . runReaderT -- | A path to a Couch DB Object. type Path = String -- | Represents a revision of a Couch DB Document. type Revision = T.Text -- | 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'. couch :: MonadCouch m => HT.Method -- ^ Method -> Path -- ^ The dbname from the connection is -- prepended to this path. Just set empty -- if you need access to many DBs. -> HT.Query -- ^ Query arguments -> Iteratee B.ByteString m a -- ^ Iteratee to process the response if no -- error occurs. -> H.RequestBody m -- ^ Body -> Iteratee B.ByteString m a couch m p q i= couch' m p [] q (const i) -- | The most general method of accessing CouchDB. This is a very thin wrapper -- around 'H.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. couch' :: MonadCouch m => HT.Method -- ^ Method -> Path -- ^ The dbname from the connection is -- prepended to this path. Just set empty -- if you need access to many DBs. -> HT.RequestHeaders -- ^ Headers -> HT.Query -- ^ Query arguments -> (HT.ResponseHeaders -> Iteratee B.ByteString m a) -- ^ Function what returns Iteratee to -- process the response if no error occurs. -> H.RequestBody m -- ^ Body -> Iteratee B.ByteString m a couch' m p h q i b = Iteratee $ do conn <- couchConnection let req = H.def { H.method = m , H.host = host conn , H.requestHeaders = h , H.port = port conn , H.path = BU8.fromString ("/" ++ dbname conn ++ "/" ++ p) , H.queryString = q , H.requestBody = b } runIteratee $ H.http req (\s h1 -> tryAccept s h1 i) (manager conn) -- | Create CouchDB database regardless of presence. Roughly equivalent to -- -- > couchPut_ "" [] $ object [] -- -- but catches 'CouchError' /412/. couchPutDb :: MonadCouch m => Path -- ^ If you passed a database name to 'withCouchConnection', -- 'runCouch', or 'CouchConnection', the path should be -- the empty string. If you passed the empty string to -- 'CouchConnection', then the dbname should be used here. -> m () couchPutDb p = catch (couchPut_ p [] $ A.object []) handler where handler (CouchError (Just 412) _) = return () handler e = throw e -- | Delete a database. couchDeleteDb :: MonadCouch m => Path -- ^ If you passed a database name to 'withCouchConnection', -- 'runCouch', or 'CouchConnection', the path should be -- the empty string. If you passed the empty string to -- 'CouchConnection', then the dbname should be used here. -> m () couchDeleteDb p = run_ $ couch HT.methodDelete p [] (yield () EOF) (H.RequestBodyBS B.empty) -- | Get Revision of a document. couchRev :: MonadCouch m => Path -> m Revision couchRev p = do v <- run_ $ couch' HT.methodHead p [] [] getEtag (H.RequestBodyBS B.empty) return $ T.dropAround (=='"') $ TE.decodeUtf8 v where getEtag h = yield (fromJust $ lookup "Etag" h) EOF -- | Load a single object from couch DB. couchGet :: MonadCouch m => Path -- ^ the dbname is prepended to this string to -- form the full path. -> HT.Query -- ^ Query arguments. -> m A.Object couchGet p q = do v <- run_ $ couch HT.methodGet p q (iterParser A.json) (H.RequestBodyBS B.empty) either throw return $ valToObj v -- | Put an object in Couch DB, returning the new Revision. couchPut :: (MonadCouch m, A.ToJSON a) => Path -- ^ the dbname is prepended to this string to -- form the full path. -> HT.Query -- ^ Query arguments. -> a -- ^ The object to store. -> m Revision couchPut p q val = do v <- run_ $ couch HT.methodPut p q (iterParser A.json) body either (liftIO . throw) return (valToObj v >>= objToRev) where body = jsonToReqBody val -- | Put an object in Couch DB with revision, returning the new Revision. couchPutRev :: (MonadCouch m, A.ToJSON a) => Path -- ^ the dbname is prepended to this string to -- form the full path. -> Revision -- ^ Document revision. For new docs provide empty string. -> HT.Query -- ^ Query arguments. -> a -- ^ The object to store. -> m Revision couchPutRev p r q val = do v <- run_ $ couch' HT.methodPut p (ifMatch r) q (\_ -> iterParser A.json) body either (liftIO . throw) return (valToObj v >>= objToRev) where body = jsonToReqBody val ifMatch "" = [] ifMatch rv = [("If-Match", TE.encodeUtf8 rv)] -- | A version of 'couchPut' which ignores the return value. This is slightly -- faster than / _ <- couchPut .../ since the JSON parser is not run. couchPut_ :: (MonadCouch m, A.ToJSON a) => Path -- ^ the dbname is prepended to this string to -- form the full path. -> HT.Query -- ^ Query arguments. -> a -- ^ The object to store. -> m () couchPut_ p q val = run_ $ couch HT.methodPut p q (yield () EOF) body where body = jsonToReqBody val -- | Delete the given revision of the object. couchDelete :: MonadCouch m => Path -- ^ the dbname is prepended to this string to -- form the full path. -> Revision -- ^ Document revision. -> m () couchDelete p r = run_ $ couch HT.methodDelete p [("rev", Just $ TE.encodeUtf8 r)] (yield () EOF) (H.RequestBodyBS B.empty) -- | 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 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 couchView :: MonadCouch m => Path -- ^ \/dbname\/_design\/ is prepended to the given path. -> HT.Query -- ^ Query arguments. -> Enumerator A.Object m a couchView p q step = do s <- lift $ run $ couch HT.methodGet ("_design/" ++ p) q (parseView step) (H.RequestBodyBS B.empty) either throwError returnI s -- | 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}/ extractViewValue :: Monad m => Enumeratee A.Object A.Object m a extractViewValue = mapEither f where f v = case M.lookup "value" v of (Just (A.Object o)) -> Right o _ -> Left $ CouchError Nothing "view does not contain value" ------------------------------------------------------------------------------- --- Helper Code ------------------------------------------------------------------------------- -- | Internal try accept tryAccept :: Monad m => HT.Status -> HT.ResponseHeaders -> (HT.ResponseHeaders -> Iteratee B.ByteString m b) -> Iteratee B.ByteString m b tryAccept (HT.Status 200 _) h it = it h tryAccept (HT.Status 201 _) h it = it h tryAccept (HT.Status 202 _) h it = it h tryAccept (HT.Status 304 _) h it = it h tryAccept (HT.Status c ms) _ _ = do v <- catchError (iterParser A.json) (\_ -> yield "" EOF) throwError $ CouchError (Just c) $ msg v where msg v = BU8.toString ms ++ reason v reason (A.Object v) = case M.lookup "reason" v of Just (A.String t) -> ": " ++ T.unpack t _ -> "" reason _ = [] -- | Converts a json object into a 'H.RequestBodyLBS' jsonToReqBody :: (A.ToJSON a, Monad m) => a -> H.RequestBody m jsonToReqBody val = H.RequestBodyLBS $ A.encode val -- where -- jbuilder = AE.fromValue $ A.toJSON val -- enum (Continue k) = k (Chunks [jbuilder]) -- enum step = returnI step -- trans = BLB.fromLazyByteString . TLE.encodeUtf8 -- untrans = TLE.decodeUtf8 . BL.toLazyByteString -- | Convers a value to an object valToObj :: A.Value -> Either CouchError A.Object valToObj (A.Object o) = Right o valToObj _ = Left $ CouchError Nothing "Couch DB did not return an object" -- | Converts an object to a revision objToRev :: A.Object -> Either CouchError Revision objToRev o = case M.lookup "rev" o of (Just (A.String r)) -> Right r _ -> Left $ CouchError Nothing "unable to find revision" data CommaOrCloseBracket = Comma | CloseBracket commaOrClose :: Parser CommaOrCloseBracket commaOrClose = do skipWhile (\c -> c /= 44 && c /= 93) "Checking for next comma" w <- anyWord8 if w == 44 then return Comma else return CloseBracket -- | The main loop of processing the view rows. viewLoop :: MonadIO m => Enumeratee B.ByteString A.Object m a viewLoop (Yield a _) = return $ Yield a EOF viewLoop (Error err) = return $ Error err viewLoop (Continue k) = do v <- iterParser (A.json "json object") vobj <- case v of (A.Object o) -> return o _ -> throwError $ CouchError Nothing "view entry is not an object" step' <- lift $ runIteratee $ k $ Chunks [vobj] res <- iterParser (commaOrClose "comma or close") case res of Comma -> viewLoop step' CloseBracket -> case step' of (Continue k') -> lift $ runIteratee $ k' EOF _ -> return step' viewStart :: Parser Bool viewStart = do _ <- string "{\"total_rows\":" skipWhile (\x -> x >= 48 && x <= 57) _ <- string ",\"offset\":" skipWhile (\x -> x >= 48 && x <= 57) _ <- string ",\"rows\":[" (string "]}" >> return False) <|> return True -- | Enumeratee to parse the data returned by a view. parseView :: MonadIO m => Enumeratee B.ByteString A.Object m a parseView (Yield a _) = return $ Yield a EOF parseView (Error err) = return $ Error err parseView (Continue k) = do b <- iterParser (viewStart "start of view") if b then viewLoop $ Continue k else lift $ runIteratee $ k EOF mapEither :: (Exception e, Monad m) => (a -> Either e b) -> Enumeratee a b m c mapEither f = checkDone (continue . step) where step k EOF = yield (Continue k) EOF step k (Chunks xs) = case Prelude.mapM f xs of Left err -> throwError err Right xs' -> k (Chunks xs') >>== mapEither f -- $pool -- The 'H.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 -- or -- packages combined with the -- 'H.newManager' and 'H.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 -- 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. -- vim: set expandtab:set tabstop=4: