[Haskell-cafe] Rank-2-polymorphism problem
Martin Huschenbett
huschi at gmx.org
Fri Mar 23 09:18:50 EDT 2007
Hi,
I'm writing some database code using HSQL and had to stop on a problem
with rank-2-polymorphism that I can't solve. The essence of my code is:
module Value where
import Data.Maybe
class SqlBind a where
fromSqlValue :: String -> a
data Field
data Value
emptyValue :: Field -> Value
emptyValue _ = ...
readValue :: Field -> (forall s. SqlBind s => s) -> Value
readValue _ = ...
That works just fine. But now I want a version of readValue that has a
Maybe wrapped around the second parameter and that shall call readValue
in the case of a Just and emptyValue in the case of Nothing. But I can't
figure out how to write this function as I always get compiler errors.
My trials were:
-- The type I want to get.
readValue' :: Field -> (forall s. SqlBind s => Maybe s) -> Value
-- First trial:
readValue' fld s =
if isJust s then readValue fld (fromJust s) else emptyValue fld
-- Second trial:
readValue' fld s
| isJust s = readValue fld (fromJust s)
| otherwise = emptyValue fld
-- Third trial:
readValue' fld (Just s) = readValue fld s
readValue' fld Nothing = emptyValue fld
-- Fourth trial:
readValue fld s = case s of
Just s' -> readValue fld s'
Nothing -> emptyValue fld
But none of these trials worked. Is there any solution that works with
GHC-6.6 for now?
Thanks in advance,
Martin.
More information about the Haskell-Cafe
mailing list