Martin Huschenbett schrieb:
My thoughts were that for any class C the types
> Maybe (forall a. C a => a) (I will call it T1 for short)
and
> (forall a. C a => Maybe a) (I will call it T2 for short)
are isomorphic. Defining the isomorphism from T1 to T2 is quite simple:
iso1 :: Maybe (for
apfelmus schrieb:
For me, the fourth trial works, at least on
f :: (forall s . Num s => Maybe s) -> Int
f y = case y of
Just x -> x
Nothing -> 0
This works, because the compiler knows that x has to have type Int. But
if you want to apply a function g :: (forall a. Num
Hello Martin,
Friday, March 23, 2007, 11:37:16 PM, you wrote:
>> readValue' :: Field -> Maybe (forall s. SqlBind s => s) -> Value
> Thank you very much, that's exactly what I wanted. After reading in the
> GHC users guide about rank 2 polymorphism I thought that this is not
> possible. Chapter
Martin Huschenbett wrote:
>
> 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
Hi again,
the solutions/proposals of Ian and Iavor seem to be exactly what I need
at a first glance. But looking at them more in detail reveals some other
problems.
I also have got a function
> getFieldValueMB :: SqlBind s => Statement -> String -> Maybe s
To get Ians approach working I wou
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 ::
Ian Lynagh schrieb:
readValue' :: Field -> Maybe (forall s. SqlBind s => s) -> Value
readValue' fld s =
if isJust s then readValue fld (fromJust s) else emptyValue fld
Thank you very much, that's exactly what I wanted. After reading in the
GHC users guide about rank 2 polymorphism I thoug