Thanks Johannes!
Thanks for the cookbook recipe, i made an example where all the rows
are extracted and converted back to the original datatype, maybe this
is useful for someone else too.
{-# LANGUAGE QuasiQuotes, TypeFamilies, GeneralizedNewtypeDeriving,
TemplateHaskell, OverloadedStrings #-}
import Database.Persist
import Database.Persist.Base
import Database.Persist.Sqlite
import Database.Persist.GenericSql.Raw
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Loops (whileJust)
import Database.Persist.TH
import Data.Either (rights)
import Data.Text (Text)
share [mkPersist, mkMigrate "migrateAll"][persist|
Person
name Text
|]
main :: IO ()
main = withSqliteConn ":memory:" $ runSqlConn $ do
runMigration migrateAll
insert $ Person "Michael Snoyman"
insert $ Person "Miriam Snoyman"
insert $ Person "Eliezer Snoyman"
insert $ Person "Gavriella Snoyman"
insert $ Person "Greg Weber"
insert $ Person "Rick Richardson"
lol <- withStmt "SELECT name FROM \"Person\";"
([]::[PersistValue]) $ \pop -> whileJust pop
(return.fromPersistValues)
liftIO $ print (rights lol::[Person])
_______________________________________________
web-devel mailing list
web-devel@haskell.org
http://www.haskell.org/mailman/listinfo/web-devel