
Hi all,
Below my .sig is a little Persist/Esqueleto program that works correctly.
The getUserCount function does thr right thing and returns the number of
rows in the User table. However, what I'd like is a generic function
that returns the row count of any table, something vaguely like this:
queryRowCount :: tableType -> SqlPersist IO Int64
queryRowCount tableName = do
[Value x] <- select . from $ \(_ :: SqlExpr (Entity tableName)) ->
return countRows
return x
Is there any way to do this? Its probably possible in Agda, but can it
be made to work with GHC?
Cheers,
Erik
--
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/
{-# LANGUAGE FlexibleContexts, GADTs, GeneralizedNewtypeDeriving, OverloadedStrings,
QuasiQuotes, ScopedTypeVariables, TypeFamilies, TemplateHaskell #-}
import Control.Monad (void)
import Control.Monad.IO.Class (liftIO)
import Database.Esqueleto
import Database.Persist.Sqlite
import Database.Persist.TH
import GHC.Int (Int64)
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
User
firstName String
lastName String
emailAddress String
UserName firstName lastName
deriving Show
Project
name String
description String
deriving Show
|]
-- This works, but only for the User table.
queryUserCount :: SqlPersist IO Int64
queryUserCount = do
[Value x] <- select . from $ \(_ :: SqlExpr (Entity User)) ->
return countRows
return x
main :: IO ()
main = withSqliteConn ":memory:" $ runSqlConn $ do
void $ runMigrationSilent migrateAll
void $ insert $ User "Fred" "Smith" "

Well, there obviously is a problem in your example code. The argument "tableName" does not live in the world of types, so /SqlExpr (Entity tableName)/ is meaningless (this barrier is getting fuzzier with each version of GHC, but well...). Perhaps something can be done with existential types ? Le 24/11/12 12:07, Erik de Castro Lopo a écrit :
Hi all,
Below my .sig is a little Persist/Esqueleto program that works correctly.
The getUserCount function does thr right thing and returns the number of rows in the User table. However, what I'd like is a generic function that returns the row count of any table, something vaguely like this:
queryRowCount :: tableType -> SqlPersist IO Int64 queryRowCount tableName = do [Value x] <- select . from $ \(_ :: SqlExpr (Entity tableName)) -> return countRows return x
Is there any way to do this? Its probably possible in Agda, but can it be made to work with GHC?
Cheers, Erik

On Sat, Nov 24, 2012 at 12:07 PM, Erik de Castro Lopo
Hi all,
Below my .sig is a little Persist/Esqueleto program that works correctly.
The getUserCount function does thr right thing and returns the number of rows in the User table. However, what I'd like is a generic function that returns the row count of any table, something vaguely like this:
queryRowCount :: tableType -> SqlPersist IO Int64 queryRowCount tableName = do [Value x] <- select . from $ \(_ :: SqlExpr (Entity tableName)) -> return countRows return x
Is there any way to do this? Its probably possible in Agda, but can it be made to work with GHC?
How about something like this: {-# LANGUAGE ScopedTypeVariables #-} queryRowCount :: forall tableType. Proxy tableType -> SqlPersist IO Int64 queryRowCount _ = do [Value x] <- select . from $ \(_ :: SqlExpr (Entity tableType)) -> return countRows return x The Proxy type is defined as: data Proxy a = Proxy You can use the 'tagged' package to get it. ScopedTypeVariables and the explicit forall are needed to make sure the type 'tableType' from the top level signature is the same as the one used later. Erik
participants (3)
-
Erik de Castro Lopo
-
Erik Hesselink
-
Gaël Deest