
Here are some functional programming job opportunities that were posted recently: Haskell Developer at Zalora http://functionaljobs.com/jobs/8678-haskell-developer-at-zalora Cheers, Sean Murphy FunctionalJobs.com

Hello Cafe, I'm playing with Persistent and have modules that I'd like to use on several backends. This is simplified situation. In shared module: sqliteRun, postgresRun :: Text -> Int -> (ConnectionPool -> IO a) -> IO a sqliteRun = withSqlitePool postgresRun conStr = withPostgresqlPool (encodeUtf8 conStr) sqlRun :: Text -> Int -> SqlPersistM a -> IO a sqlRun conStr poolSize = postgresRun conStr poolSize . runSqlPersistMPool --sqlRun conStr poolSize = sqliteRun conStr poolSize . runSqlPersistMPool All works well if either 'sqlRun' above is commented/uncommented: In one of modules: data ThingCfg = ThingCfg { thingDb :: Text } listThings :: ThingCfg -> IO [Thing] listThings db = sqlRun (thingDb db) $ selectList ... findThing :: ThingId -> ThingCfg -> IO (Maybe Thing) findThing uid db = sqlRun (thingDb db) $ getBy ... On call site simply: let tdb = ThingCfg "test" ts <- listThings tdb I would like to specify 'sqliteRun' or 'postgresRun' function as (some) parameter on the call site, but do not know how. Something of imaginary solution: data ThingCfg = ThingCfg { thingDb :: Text, thingRun :: SqlPersistM a -> IO a } On call site: let tdb = ThingCfg "test" sqliteRun ts <- listThings tdb I want to keep it as an init param because there are other backends (class instances) that are not Persistent, so the use of 'sqlRun' on call site is not an option. What would be the best/correct way(s) to achieve that? Best regards, Vlatko

Hi Vlatko,
Did you consider:
{-# LANGUAGE RankNTypes #-}
data ThingCfg m = ThingCfg {
thingDb :: Text,
thingRun_ :: forall a. Text -> m a -> IO a }
thingRun (ThingCfg db f) = f db
Maybe the `m' above should be SqlPersistM, if all your other backends use
that type.
--
Adam
On Tue, Jan 28, 2014 at 1:37 PM, Vlatko Basic
Hello Cafe,
I'm playing with Persistent and have modules that I'd like to use on several backends. This is simplified situation.
In shared module:
sqliteRun, postgresRun :: Text -> Int -> (ConnectionPool -> IO a) -> IO a sqliteRun = withSqlitePool postgresRun conStr = withPostgresqlPool (encodeUtf8 conStr)
sqlRun :: Text -> Int -> SqlPersistM a -> IO a sqlRun conStr poolSize = postgresRun conStr poolSize . runSqlPersistMPool --sqlRun conStr poolSize = sqliteRun conStr poolSize . runSqlPersistMPool
All works well if either 'sqlRun' above is commented/uncommented:
In one of modules:
data ThingCfg = ThingCfg { thingDb :: Text }
listThings :: ThingCfg -> IO [Thing] listThings db = sqlRun (thingDb db) $ selectList ...
findThing :: ThingId -> ThingCfg -> IO (Maybe Thing) findThing uid db = sqlRun (thingDb db) $ getBy ...
On call site simply: let tdb = ThingCfg "test" ts <- listThings tdb
I would like to specify 'sqliteRun' or 'postgresRun' function as (some) parameter on the call site, but do not know how. Something of imaginary solution:
data ThingCfg = ThingCfg { thingDb :: Text, thingRun :: SqlPersistM a -> IO a }
On call site: let tdb = ThingCfg "test" sqliteRun ts <- listThings tdb
I want to keep it as an init param because there are other backends (class instances) that are not Persistent, so the use of 'sqlRun' on call site is not an option.
What would be the best/correct way(s) to achieve that?
Best regards, Vlatko _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
adam vogt
-
Functional Jobs
-
Vlatko Basic