[Haskell-cafe] Re: Ambiguous type with PolymorphicComponents

Daniel Fischer daniel.is.fischer at web.de
Sat Mar 7 16:11:21 EST 2009


Am Samstag, 7. März 2009 21:48 schrieb Maurí­cio:
>  >> (...)
> >
> > When you have
> >
> > data Test = Test (forall w. (C1 w, C2 w, ..., Cn w) => w)
> >
> > and
> >
> > function (Test w) = classmethod w,
> >
> > there is no way to decide which instance to use, hence the type variable
> > is ambiguous.
> > (...)
>
> But, then, how can I reach the data inside a
> polymorphic component? Or, better, what can I
> do with it? If I say:
>
> function (Test w) = classmethod (w :: specificType)
>
> then I have to suppose that w is always of
> 'specificType', and this may not be true.

If

w :: forall a. (Class a) => a,

then w is (can be) of all specific types which are instances of Class.

Perhaps what you wanted was an existential type:

{-# LANGUAGE ExistentialQuantification #-}

data ETest = forall w. WidgetClass w => ETest w

?

Or a GADT:

data GTest where
	GTest :: forall a. WidgetClass a => a -> GTest

?

>
> Thanks,
> Maurício
>

Cheers,
Daniel



More information about the Haskell-Cafe mailing list