[Haskell-cafe] couchDB
Andrew U. Frank
frank22 at geoinfo.tuwien.ac.at
Fri Jul 30 03:31:10 EDT 2010
a few weeks ago a question was posed on this list for examples how to
use couchDB. i post the 'hello world' for couchDB using the haskell
interface - perhaps it helps other to start!
a more extensive and complicate example is found at
www.maztravel.com/haskell/mySqlToCouchDB.html
I created with Futon a db names "first" (i had no luck with names
containing a - or a _ , but have not investigated further). the
runcouchDB' affects the couchDB at localhost.
andrew
ps: if there is a better place to document examples? a wiki on
haskell.org would be nice and should be available for any project in
hackage.
----
{-# LANGUAGE DeriveDataTypeable #-}
module Main ( ) where
import Database.CouchDB
import Data.Data (Typeable)
import Text.JSON
s1 = JSString $ toJSString "Peter"
m1 = makeObj [("FirstName", s1), ("FamilytName", JSString . toJSString
$ "Miller")]
mydb1 = db "first" -- convert db name to checked couchdb
-- problem with "-" or "_" in db names in haskell??
main = do
putStrLn "start couchdb tests"
(doc, rev) <- runCouchDB' $ newDoc mydb1 m1 -- works
return ()
More information about the Haskell-Cafe
mailing list