module Database.CouchDB
(
CouchMonad
, runCouchDB
, runCouchDB'
, runCouchDBURI
, CouchConn()
, runCouchDBWith
, createCouchConn
, createCouchConnFromURI
, closeCouchConn
, DB
, db
, isDBString
, createDB
, dropDB
, getAllDBs
, Doc
, Rev
, doc
, rev
, isDocString
, newNamedDoc
, newDoc
, updateDoc
, bulkUpdateDocs
, deleteDoc
, forceDeleteDoc
, getDocPrim
, getDocRaw
, getDoc
, getAllDocs
, getAndUpdateDoc
, getAllDocIds
, CouchView (..)
, newView
, queryView
, queryViewKeys
) where
import Database.CouchDB.HTTP
import Control.Monad
import Control.Monad.Trans (liftIO)
import Data.Maybe (fromJust,mapMaybe,maybeToList)
import Text.JSON
import Data.List (elem)
import Data.Maybe (mapMaybe)
import Database.CouchDB.Unsafe (CouchView (..))
import qualified Data.List as L
import qualified Database.CouchDB.Unsafe as U
data DB = DB String
instance Show DB where
show (DB s) = s
instance JSON DB where
readJSON val = do
s <- readJSON val
case isDBString s of
False -> fail "readJSON: not a valid database name"
True -> return (DB s)
showJSON (DB s) = showJSON s
isDBFirstChar ch = (ch >= 'a' && ch <= 'z')
isDBOtherChar ch = (ch >= 'a' && ch <= 'z')
|| (ch >= '0' && ch <= '9') || ch `elem` "_$()+-/"
isFirstDocChar ch = (ch >= 'A' && ch <='Z') || (ch >= 'a' && ch <= 'z')
|| (ch >= '0' && ch <= '9') || ch `elem` "-@."
isDocChar ch = (ch >= 'A' && ch <='Z') || (ch >= 'a' && ch <= 'z')
|| (ch >= '0' && ch <= '9') || ch `elem` "-@._"
isDBString :: String -> Bool
isDBString [] = False
isDBString (first:[]) = isDBFirstChar first
isDBString (first:rest) = isDBFirstChar first && and (map isDBOtherChar rest)
db :: String -> DB
db dbName = case isDBString dbName of
True -> DB dbName
False -> error $ "db : invalid dbName (" ++ dbName ++ ")"
data Rev = Rev { unRev :: JSString } deriving (Eq,Ord)
instance Show Rev where
show (Rev s) = fromJSString s
data Doc = Doc { unDoc :: JSString } deriving (Eq,Ord)
instance Show Doc where
show (Doc s) = fromJSString s
instance JSON Doc where
readJSON (JSString s) | isDocString (fromJSString s) = return (Doc s)
readJSON _ = fail "readJSON: not a valid document name"
showJSON (Doc s) = showJSON s
instance Read Doc where
readsPrec _ str = maybeToList (parseFirst str) where
parseFirst "" = Nothing
parseFirst (ch:rest)
| isFirstDocChar ch =
let (chs',rest') = parseRest rest
in Just (Doc $ toJSString $ ch:chs',rest)
| otherwise = Nothing
parseRest "" = ("","")
parseRest (ch:rest)
| isDocChar ch =
let (chs',rest') = parseRest rest
in (ch:chs',rest')
| otherwise =
("",ch:rest)
rev :: String -> Rev
rev = Rev . toJSString
doc :: String -> Doc
doc docName = case isDocString docName of
True -> Doc (toJSString docName)
False -> error $ "doc : invalid docName (" ++ docName ++ ")"
isDocString :: String -> Bool
isDocString [] = False
isDocString (first:rest) = isFirstDocChar first && and (map isDocChar rest)
createDB :: String -> CouchMonad ()
createDB = U.createDB
dropDB :: String -> CouchMonad Bool
dropDB = U.dropDB
getAllDBs :: CouchMonad [DB]
getAllDBs = U.getAllDBs
>>= \dbs -> return [db $ fromJSString s | s <- dbs]
newNamedDoc :: (JSON a)
=> DB
-> Doc
-> a
-> CouchMonad (Either String Rev)
newNamedDoc dbName docName body = do
r <- U.newNamedDoc (show dbName) (show docName) body
case r of
Left s -> return (Left s)
Right rev -> return (Right $ Rev rev)
updateDoc :: (JSON a)
=> DB
-> (Doc,Rev)
-> a
-> CouchMonad (Maybe (Doc,Rev))
updateDoc db (doc,rev) val = do
r <- U.updateDoc (show db) (unDoc doc, unRev rev) val
case r of
Nothing -> return Nothing
Just (_,rev) -> return $ Just (doc,Rev rev)
bulkUpdateDocs :: (JSON a)
=> DB
-> [a]
-> CouchMonad (Maybe [Either String (Doc, Rev)])
bulkUpdateDocs db docs = do
r <- U.bulkUpdateDocs (show db) docs
case r of
Nothing -> return Nothing
Just es -> return $
Just $
map (\e ->
case e of
Left err -> Left $ fromJSString err
Right (doc, rev) -> Right (Doc doc, Rev rev)
) es
forceDeleteDoc :: DB
-> Doc
-> CouchMonad Bool
forceDeleteDoc db doc = U.forceDeleteDoc (show db) (show doc)
deleteDoc :: DB
-> (Doc,Rev)
-> CouchMonad Bool
deleteDoc db (doc,rev) = U.deleteDoc (show db) (unDoc doc,unRev rev)
newDoc :: (JSON a)
=> DB
-> a
-> CouchMonad (Doc,Rev)
newDoc db body = do
(doc,rev) <- U.newDoc (show db) body
return (Doc doc,Rev rev)
getDoc :: (JSON a)
=> DB
-> Doc
-> CouchMonad (Maybe (Doc,Rev,a))
getDoc db doc = do
r <- U.getDoc (show db) (show doc)
case r of
Nothing -> return Nothing
Just (_,rev,val) -> return $ Just (doc,Rev rev,val)
getAllDocs :: JSON a
=> DB
-> [(String, JSValue)]
-> CouchMonad [(Doc, a)]
getAllDocs db args = do
rows <- U.getAllDocs (show db) args
return $ map (\(doc,val) -> (Doc doc,val)) rows
getDocPrim :: DB
-> Doc
-> CouchMonad (Maybe (Doc,Rev,[(String,JSValue)]))
getDocPrim db doc = do
r <- U.getDocPrim (show db) (show doc)
case r of
Nothing -> return Nothing
Just (_,rev,obj) -> return $ Just (doc,Rev rev,obj)
getDocRaw :: DB -> Doc -> CouchMonad (Maybe String)
getDocRaw db doc = U.getDocRaw (show db) (show doc)
getAndUpdateDoc :: (JSON a)
=> DB
-> Doc
-> (a -> IO a)
-> CouchMonad (Maybe Rev)
getAndUpdateDoc db docId fn = do
r <- U.getAndUpdateDoc (show db) (show docId) fn
case r of
Nothing -> return Nothing
Just rev -> return $ Just (Rev $ toJSString rev)
getAllDocIds ::DB
-> CouchMonad [Doc]
getAllDocIds db = do
allIds <- U.getAllDocIds (show db)
return (map Doc allIds)
newView :: String
-> String
-> [CouchView]
-> CouchMonad ()
newView = U.newView
queryView :: (JSON a)
=> DB
-> Doc
-> Doc
-> [(String, JSValue)]
-> CouchMonad [(Doc, a)]
queryView db viewSet view args = do
rows <- U.queryView (show db) (show viewSet) (show view) args
return $ map (\(doc,val) -> (Doc doc,val)) rows
queryViewKeys :: DB
-> Doc
-> Doc
-> [(String, JSValue)]
-> CouchMonad [Doc]
queryViewKeys db viewSet view args = do
rows <- U.queryViewKeys (show db) (show viewSet) (show view) args
return $ map (Doc . toJSString) rows