[Haskell-cafe] Re: Rank-2-polymorphism problem

Iavor Diatchki iavor.diatchki at gmail.com
Fri Mar 23 16:48:49 EDT 2007


Hello,
What Ian suggested is a very GHC 6.6 specific solution that uses much
more that simply rank-2 types.  Here is another solution that uses
just rank-2 types (and, by the way, all type signatures are optional,
as in ordinary Haskell):

module Value where

class SqlBind a where
  fromSqlValue :: String -> a

data Field
data Value

emptyValue :: Field -> Value
emptyValue _ = undefined

data Binder = Binder (forall s. SqlBind s => s)

readValue :: Field -> Binder -> Value
readValue _ (Binder _) = undefined

readOptValue :: Field -> Maybe Binder -> Value
readOptValue f x = maybe (emptyValue f) (readValue f) x


Hope this helps
-Iavor


More information about the Haskell-Cafe mailing list