Up-to-date HaskellDB sample or tute

Hi All, All the tutorials and samples I can find for HaskellDB seem to be bitrotten. Does anybody know of a newish one? I just want to connect to a postgres DB and run some simple queries. Or is HaskellDB superseded now? TIA, Adrian.

How about these? http://users.utu.fi/machra/posts/2012-08-23-relalgebra.html http://users.utu.fi/machra/posts/2011-07-15-haskelldb.html these shouldn't be that bitrotted. There has been some updates to haskelldb, but nothing too big. Oh and btw, sorry for the horrible layout On Wed, Jul 10, 2013 at 05:57:41PM +0800, Adrian May wrote:
Hi All,
All the tutorials and samples I can find for HaskellDB seem to be bitrotten. Does anybody know of a newish one? I just want to connect to a postgres DB and run some simple queries.
Or is HaskellDB superseded now?
TIA, Adrian.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Mats Rauhala MasseR

Thanks! At first sight they look compatible with what I've been finding
out. But I suspect that haskelldb-th with it's CodeGen module is history. I
just got that bit working like this:
{-# LANGUAGE TemplateHaskell #-}
import Database.HaskellDB
import Database.HaskellDB.DBSpec
import Database.HaskellDB.DBSpec.PPHelpers
import Database.HaskellDB.HDBC
import Database.HaskellDB.HDBC.PostgreSQL
import Database.HaskellDB.DBSpec.DBSpecToDBDirect
-- These work after the dbInfoToModuleFiles run ...
--import Adsdb
--import Adsdb.Test
adsDB :: (Database -> IO a) -> IO a
adsDB = postgresqlConnect adsdb_opts
adsdb_opts = [("host","localhost")
,("user","ad")
,("password","1wd1wd")
,("dbname","adsdb")]
dbinfo :: DBInfo
dbinfo = makeDBSpec "Adsdb"
(DBOptions { useBString = False , makeIdent =
mkIdentPreserving })
[ makeTInfo "Test"
[ makeCInfo "teststring" (StringT, False)
, makeCInfo "testint" (IntT, False)
]
]
main = dbInfoToModuleFiles "." "Adsdb" dbinfo
but when I import the generated code it warns like this:
Adsdb.hs:12:24:
Warning: Fields of `DBOptions' not initialised: makeIdent
In the `opts' field of a record
In the expression:
DBInfo
{dbname = "Adsdb", opts = DBOptions {useBString = False},
tbls = [TInfo
{tname = "Test",
cols = [CInfo {cname = "teststring", descr = ...},
....]}]}
In an equation for `adsdb':
adsdb
= DBInfo
{dbname = "Adsdb", opts = DBOptions {useBString = False},
tbls = [TInfo {tname = "Test", cols = [...]}]}
Adrian.
On 10 July 2013 19:25, Mats Rauhala
How about these?
http://users.utu.fi/machra/posts/2012-08-23-relalgebra.html http://users.utu.fi/machra/posts/2011-07-15-haskelldb.html
these shouldn't be that bitrotted. There has been some updates to haskelldb, but nothing too big. Oh and btw, sorry for the horrible layout
On Wed, Jul 10, 2013 at 05:57:41PM +0800, Adrian May wrote:
Hi All,
All the tutorials and samples I can find for HaskellDB seem to be bitrotten. Does anybody know of a newish one? I just want to connect to a postgres DB and run some simple queries.
Or is HaskellDB superseded now?
TIA, Adrian.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Mats Rauhala MasseR
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (2)
-
Adrian May
-
Mats Rauhala