[web-devel] RawSql

Greg Weber greg at gregweber.info
Sun Jun 19 20:10:11 CEST 2011


Thanks Johannes!

Can you make sure this compiles and then add it to the wiki:
http://www.yesodweb.com/show/topic/376
Let us know if there are any difficulties with the wiki, as it is new
software. There are a couple more things we need to add to make it nicer to
use.

Greg Weber

On Sat, Jun 18, 2011 at 11:53 AM, Johannes Hess
<zerstroyer at googlemail.com>wrote:

> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110619/304ec6ee/attachment.htm>


More information about the web-devel mailing list