Safe Haskell | None |
---|---|
Language | Haskell2010 |
Interface to CouchDB.
Synopsis
- data CouchMonad a
- runCouchDB :: String -> Int -> CouchMonad a -> IO a
- runCouchDB' :: CouchMonad a -> IO a
- runCouchDBURI :: URI -> CouchMonad a -> IO a
- data CouchConn
- runCouchDBWith :: CouchConn -> CouchMonad a -> IO a
- createCouchConn :: String -> Int -> IO CouchConn
- createCouchConnFromURI :: URI -> IO CouchConn
- closeCouchConn :: CouchConn -> IO ()
- data DB
- db :: String -> DB
- isDBString :: String -> Bool
- createDB :: String -> CouchMonad ()
- dropDB :: String -> CouchMonad Bool
- getAllDBs :: CouchMonad [DB]
- data Doc
- data Rev
- doc :: String -> Doc
- rev :: String -> Rev
- isDocString :: String -> Bool
- newNamedDoc :: JSON a => DB -> Doc -> a -> CouchMonad (Either String Rev)
- newDoc :: JSON a => DB -> a -> CouchMonad (Doc, Rev)
- updateDoc :: JSON a => DB -> (Doc, Rev) -> a -> CouchMonad (Maybe (Doc, Rev))
- bulkUpdateDocs :: JSON a => DB -> [a] -> CouchMonad (Maybe [Either String (Doc, Rev)])
- deleteDoc :: DB -> (Doc, Rev) -> CouchMonad Bool
- forceDeleteDoc :: DB -> Doc -> CouchMonad Bool
- getDocPrim :: DB -> Doc -> CouchMonad (Maybe (Doc, Rev, [(String, JSValue)]))
- getDocRaw :: DB -> Doc -> CouchMonad (Maybe String)
- getDoc :: JSON a => DB -> Doc -> CouchMonad (Maybe (Doc, Rev, a))
- getAllDocs :: JSON a => DB -> [(String, JSValue)] -> CouchMonad [(Doc, a)]
- getAndUpdateDoc :: JSON a => DB -> Doc -> (a -> IO a) -> CouchMonad (Maybe Rev)
- getAllDocIds :: DB -> CouchMonad [Doc]
- data CouchView
- newView :: String -> String -> [CouchView] -> CouchMonad ()
- queryView :: JSON a => DB -> Doc -> Doc -> [(String, JSValue)] -> CouchMonad [(Doc, a)]
- queryViewKeys :: DB -> Doc -> Doc -> [(String, JSValue)] -> CouchMonad [Doc]
Initialization
data CouchMonad a Source #
A computation that interacts with a CouchDB database. This monad
encapsulates the IO
monad, a persistent HTTP connnection to a
CouchDB database and enough information to re-open the connection
if it is closed.
Instances
Monad CouchMonad Source # | |
Defined in Database.CouchDB.HTTP (>>=) :: CouchMonad a -> (a -> CouchMonad b) -> CouchMonad b # (>>) :: CouchMonad a -> CouchMonad b -> CouchMonad b # return :: a -> CouchMonad a # fail :: String -> CouchMonad a # | |
Functor CouchMonad Source # | |
Defined in Database.CouchDB.HTTP fmap :: (a -> b) -> CouchMonad a -> CouchMonad b # (<$) :: a -> CouchMonad b -> CouchMonad a # | |
Applicative CouchMonad Source # | |
Defined in Database.CouchDB.HTTP pure :: a -> CouchMonad a # (<*>) :: CouchMonad (a -> b) -> CouchMonad a -> CouchMonad b # liftA2 :: (a -> b -> c) -> CouchMonad a -> CouchMonad b -> CouchMonad c # (*>) :: CouchMonad a -> CouchMonad b -> CouchMonad b # (<*) :: CouchMonad a -> CouchMonad b -> CouchMonad a # | |
MonadIO CouchMonad Source # | |
Defined in Database.CouchDB.HTTP liftIO :: IO a -> CouchMonad a # |
:: String | hostname |
-> Int | port |
-> CouchMonad a | |
-> IO a |
runCouchDB' :: CouchMonad a -> IO a Source #
Connects to the CouchDB server at localhost:5984.
:: URI | URI to connect |
-> CouchMonad a | |
-> IO a |
Explicit Connections
Describes a connection to a CouchDB database. This type is
encapsulated by CouchMonad
.
runCouchDBWith :: CouchConn -> CouchMonad a -> IO a Source #
Run a CouchDB computation with an existing CouchDB connection.
Create a CouchDB connection for use with runCouchDBWith.
createCouchConnFromURI Source #
Create a CouchDB from an URI connection for use with runCouchDBWith.
closeCouchConn :: CouchConn -> IO () Source #
Closes an open CouchDB connection
Databases
isDBString :: String -> Bool Source #
createDB :: String -> CouchMonad () Source #
Creates a new database. Throws an exception if the database already exists.
getAllDBs :: CouchMonad [DB] Source #
Documents
Document name
isDocString :: String -> Bool Source #
:: JSON a | |
=> DB | database name |
-> a | document body |
-> CouchMonad (Doc, Rev) | id and rev of new document |
:: DB | database |
-> Doc | document identifier |
-> CouchMonad Bool |
Delete a doc by document identifier (revision number not needed). This operation first retreives the document to get its revision number. It fails if the document doesn't exist or there is a conflict.
:: DB | database name |
-> Doc | document name |
-> CouchMonad (Maybe (Doc, Rev, [(String, JSValue)])) |
|
Gets a document as a raw JSON value. Returns the document id,
revision and value as a JSObject
. These fields are queried lazily,
and may fail later if the response from the server is malformed.
:: DB | database name |
-> CouchMonad [Doc] |
Views
Creating and querying views