Ambiguous type with PolymorphicComponents

Hi, When reading this code in ghci, I get an ambiguous type at last line: {-# LANGUAGE PolymorphicComponents #-} {-# LANGUAGE RankNTypes #-} import Graphics.UI.Gtk data Test = Test (forall w. WidgetClass w => w) toAction (Test w) = toWidget w It's interesting that if I replace 'Integral' for 'WidgetClass' and 'toInteger' for 'toWidget', I get no error messages, and I see no essencial diference between both classes and both functions. Do you know what am I missing? Thanks, Maurício

Am Samstag, 7. März 2009 20:28 schrieb Maurício:
Hi,
When reading this code in ghci, I get an ambiguous type at last line:
{-# LANGUAGE PolymorphicComponents #-} {-# LANGUAGE RankNTypes #-} import Graphics.UI.Gtk data Test = Test (forall w. WidgetClass w => w) toAction (Test w) = toWidget w
It's interesting that if I replace 'Integral' for 'WidgetClass' and 'toInteger' for 'toWidget', I get no error messages, and I see no essencial diference between both classes and both functions.
Do you know what am I missing?
Type defaulting. 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 if at least one of these classes is numeric and all of the classes are defined in the standard libraries, then (section 4.3.4 of the report, IIRC) the ambiguous type variable is defaultable. In the case of Integral and toInteger, defaulting kicks in and defaults the type to Integer (unless you specified other defaults): {-# LANGUAGE PolymorphicComponents #-} {-# LANGUAGE RankNTypes #-} data Test = Test (forall w. (Show w, Integral w) => w) toAction (Test w) = show w $ ghci Polymorph -fwarn-type-defaults GHCi, version 6.8.3: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. [1 of 1] Compiling Main ( Polymorph.hs, interpreted ) Polymorph.hs:6:25: Warning: Defaulting the following constraint(s) to type `Integer' `Integral w' arising from a use of `w' at Polymorph.hs:6:25 In the first argument of `show', namely `w' In the expression: show w In the definition of `toAction': toAction (Test w) = show w Ok, modules loaded: Main. *Main> If you really want the contents of Test to bepolymorphic, before you use it, you must cast it to some specific type, toAction (Test w) = toWidget (w :: SomeSpecificWidget) should work.
Thanks, Maurício
Cheers, Daniel

(...)
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. Thanks, Maurício

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
participants (2)
-
Daniel Fischer
-
Maurício