| Safe Haskell | None |
|---|
Database.CouchDB.Conduit.Explicit
Description
Explicit methods for CouchDB documents. Documents represents in "good
old" aeson manner through ToJSON and FromJSON.
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
import Control.Applicative ((<$>), (<*>))
import Control.Monad.IO.Class (liftIO)
import Data.Aeson
import Database.CouchDB.Conduit
import Database.CouchDB.Conduit.Explicit
-- | Our doc with instances
data D = D { f1 :: Int, f2 :: String } deriving (Show)
instance FromJSON D where
parseJSON (Object v) = D <$> v .: "f1" <*> v .: "f2"
parseJSON _ = mzero
instance ToJSON D where
toJSON (D f1 f2) = object ["f1" .= f1, "f2" .= f2]
runCouch def $ do
-- Put new doc and update it
rev1 <- couchPut "mydb" "my-doc1" "" [] $ D 123 "str"
rev2 <- couchPut "mydb" "my-doc1" rev1 [] $ D 1234 "another"
-- get it and print
(rev3, d1 :: D) <- couchGet "mydb" "my-doc1" []
liftIO $ print d1
-- update it in brute-force manner
couchPut' "mydb" "my-doc1" [] $ D 12345 "third" -- notice - no rev
-- get revision and delete
rev3 <- couchRev "mydb" "my-doc1"
couchDelete "mydb" "my-doc1" rev3
For details of types see Data.Aeson. To work with documents in generic manner, look at Database.CouchDB.Conduit.Generic.
- couchGet :: (MonadCouch m, FromJSON a) => Path -> Path -> Query -> m (Revision, a)
- couchPut :: (MonadCouch m, ToJSON a) => Path -> Path -> Revision -> Query -> a -> m Revision
- couchPut_ :: (MonadCouch m, ToJSON a) => Path -> Path -> Query -> a -> m Revision
- couchPut' :: (MonadCouch m, ToJSON a) => Path -> Path -> Query -> a -> m Revision
- toType :: (MonadResource m, FromJSON a) => Conduit Value m a
Accessing documents
Manipulating documents
Arguments
| :: (MonadCouch m, ToJSON a) | |
| => Path | Database |
| -> Path | Document path |
| -> Query | Query arguments. |
| -> a | The object to store. |
| -> m Revision |
"Don't care" version of couchPut. Creates document only in its
absence.
Arguments
| :: (MonadCouch m, ToJSON a) | |
| => Path | Database |
| -> Path | Document path |
| -> Query | Query arguments. |
| -> a | The object to store. |
| -> m Revision |
Brute force version of couchPut. Creates a document regardless of
presence.
Working with views
toType :: (MonadResource m, FromJSON a) => Conduit Value m aSource
Convert CouchDB view row or row value from Database.CouchDB.Conduit.View
to concrete FromJSON type.
res <- couchView "mydesign" "myview" [] $ rowValue =$= toType =$ consume