How to present the commonness of some objects?

Hi, I thought "class" was for this purpose. But it turns out not. Code as following could not compiled. 1 main = do 2 mapM_ (\(x, y, widget) -> do 3 a <- widgetRun widget 4 putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) => [(Integer, Integer, w)] 8 widgetList = [] 9 10 class Widget w where 11 widgetRun :: w -> IO () --- % ghc --make tmp/test.hs [1 of 1] Compiling Main ( tmp/test.hs, /tmp/Main.o ) tmp/test.hs:3:16: Ambiguous type variable `t' in the constraint: `Widget t' arising from a use of `widgetRun' at tmp/test.hs:3:16-31 Probable fix: add a type signature that fixes these type variable(s) -- 竹密岂妨流水过 山高哪阻野云飞

You have a couple problems here. The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic. The second is that it looks like you probably want a heterogeneous list of widgets -- that is, possibly different types of widget as long as they all conform to Widget. To do this you'll need ExistentialQuantification (or GADTs I guess?). For example: {-# LANGUAGE ExistentialQuantification #-} class Widget w where widgetRun :: w -> IO () data SomeWidget = forall w. Widget w => SomeWidget w widgetList :: [(Integer, Integer, SomeWidget)] widgetList = [] main = mapM aux widgetList aux (x, y, sw) = case sw of SomeWidget w -> widgetRun w Note that the type variable for widgetList 'w' has disappeared. Before, with the type variable 'w', all elements of the widgetList had to be of the same type (lists being homogeneous). By wrapping up the type variable 'w' inside SomeWidget, you can now have whatever types of widgets in that SomeWidget, e.g. data Button = Button (IO ()) instance Widget Button where widgetRun = ... data Label = Label (String -> IO ()) instance Widget Label where widgetRun = ... widgetList:: [(Integer, Integer, SomeWidget)] widgetList = [ SomeWidget (Button $ putStrLn "ding!") , SomeWidget (Label $ putStrLn . ("entered: " ++)) ] Before, without existential quantification, you had to have all the same type of widget (e.g. all Button or all Label) Hope this makes it more clear. -Ross On Jul 3, 2009, at 12:00 AM, Magicloud Magiclouds wrote:
Hi, I thought "class" was for this purpose. But it turns out not. Code as following could not compiled.
1 main = do 2 mapM_ (\(x, y, widget) -> do 3 a <- widgetRun widget 4 putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) => [(Integer, Integer, w)] 8 widgetList = [] 9 10 class Widget w where 11 widgetRun :: w -> IO () --- % ghc --make tmp/test.hs [1 of 1] Compiling Main ( tmp/test.hs, /tmp/Main.o )
tmp/test.hs:3:16: Ambiguous type variable `t' in the constraint: `Widget t' arising from a use of `widgetRun' at tmp/test.hs: 3:16-31 Probable fix: add a type signature that fixes these type variable(s) -- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Wow, this complex.... Thank you. I will try that.
On Fri, Jul 3, 2009 at 12:24 PM, Ross Mellgren
You have a couple problems here.
The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic.
The second is that it looks like you probably want a heterogeneous list of widgets -- that is, possibly different types of widget as long as they all conform to Widget. To do this you'll need ExistentialQuantification (or GADTs I guess?).
For example:
{-# LANGUAGE ExistentialQuantification #-}
class Widget w where widgetRun :: w -> IO ()
data SomeWidget = forall w. Widget w => SomeWidget w
widgetList :: [(Integer, Integer, SomeWidget)] widgetList = []
main = mapM aux widgetList aux (x, y, sw) = case sw of SomeWidget w -> widgetRun w
Note that the type variable for widgetList 'w' has disappeared. Before, with the type variable 'w', all elements of the widgetList had to be of the same type (lists being homogeneous). By wrapping up the type variable 'w' inside SomeWidget, you can now have whatever types of widgets in that SomeWidget, e.g.
data Button = Button (IO ()) instance Widget Button where widgetRun = ...
data Label = Label (String -> IO ()) instance Widget Label where widgetRun = ...
widgetList:: [(Integer, Integer, SomeWidget)] widgetList = [ SomeWidget (Button $ putStrLn "ding!") , SomeWidget (Label $ putStrLn . ("entered: " ++)) ]
Before, without existential quantification, you had to have all the same type of widget (e.g. all Button or all Label)
Hope this makes it more clear.
-Ross
On Jul 3, 2009, at 12:00 AM, Magicloud Magiclouds wrote:
Hi, I thought "class" was for this purpose. But it turns out not. Code as following could not compiled.
1 main = do 2 mapM_ (\(x, y, widget) -> do 3 a <- widgetRun widget 4 putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) => [(Integer, Integer, w)] 8 widgetList = [] 9 10 class Widget w where 11 widgetRun :: w -> IO () --- % ghc --make tmp/test.hs [1 of 1] Compiling Main ( tmp/test.hs, /tmp/Main.o )
tmp/test.hs:3:16: Ambiguous type variable `t' in the constraint: `Widget t' arising from a use of `widgetRun' at tmp/test.hs:3:16-31 Probable fix: add a type signature that fixes these type variable(s) -- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 竹密岂妨流水过 山高哪阻野云飞

On Thu, Jul 2, 2009 at 8:32 PM, Magicloud Magiclouds < magicloud.magiclouds@gmail.com> wrote:
Wow, this complex.... Thank you. I will try that.
No, don't! There is an easier way. Don't use a class, just use a record. I would translate your class as: data Widget = Widget { widgetRun :: IO () } If you need more capabilities, add them as fields in this record. There is no need for typeclasses here. Keep in mind that with this solution *and* with the ExistentialQuantification solution, there is no possibility of downcasting. I.e. if you were planning on making a GraphicalWidget subclass, and them somewhere seeing if a a Widget is actually a GraphicalWidget, you will be disappointed. The solution in this case is to redesign your software not to need downcasting. This is the point at which you are forced to move away from OO thinking. Luke
On Fri, Jul 3, 2009 at 12:24 PM, Ross Mellgren
wrote: You have a couple problems here.
The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic.
The second is that it looks like you probably want a heterogeneous list of widgets -- that is, possibly different types of widget as long as they all conform to Widget. To do this you'll need ExistentialQuantification (or GADTs I guess?).
For example:
{-# LANGUAGE ExistentialQuantification #-}
class Widget w where widgetRun :: w -> IO ()
data SomeWidget = forall w. Widget w => SomeWidget w
widgetList :: [(Integer, Integer, SomeWidget)] widgetList = []
main = mapM aux widgetList aux (x, y, sw) = case sw of SomeWidget w -> widgetRun w
Note that the type variable for widgetList 'w' has disappeared. Before, with the type variable 'w', all elements of the widgetList had to be of the same type (lists being homogeneous). By wrapping up the type variable 'w' inside SomeWidget, you can now have whatever types of widgets in that SomeWidget, e.g.
data Button = Button (IO ()) instance Widget Button where widgetRun = ...
data Label = Label (String -> IO ()) instance Widget Label where widgetRun = ...
widgetList:: [(Integer, Integer, SomeWidget)] widgetList = [ SomeWidget (Button $ putStrLn "ding!") , SomeWidget (Label $ putStrLn . ("entered: " ++)) ]
Before, without existential quantification, you had to have all the same type of widget (e.g. all Button or all Label)
Hope this makes it more clear.
-Ross
On Jul 3, 2009, at 12:00 AM, Magicloud Magiclouds wrote:
Hi, I thought "class" was for this purpose. But it turns out not. Code as following could not compiled.
1 main = do 2 mapM_ (\(x, y, widget) -> do 3 a <- widgetRun widget 4 putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) => [(Integer, Integer, w)] 8 widgetList = [] 9 10 class Widget w where 11 widgetRun :: w -> IO () --- % ghc --make tmp/test.hs [1 of 1] Compiling Main ( tmp/test.hs, /tmp/Main.o )
tmp/test.hs:3:16: Ambiguous type variable `t' in the constraint: `Widget t' arising from a use of `widgetRun' at tmp/test.hs:3:16-31 Probable fix: add a type signature that fixes these type variable(s) -- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2009/7/3 Luke Palmer
Keep in mind that with this solution *and* with the ExistentialQuantification solution, there is no possibility of downcasting. I.e. if you were planning on making a GraphicalWidget subclass, and them somewhere seeing if a a Widget is actually a GraphicalWidget, you will be disappointed. The solution in this case is to redesign your software not to need downcasting. This is the point at which you are forced to move away from OO thinking.
Heck, as far as I'm aware most OO communities frown on downcasting too. The "OO approach" is to call a virtual method and let the object decide to do, which (with enough hand-waving) is basically what you end up doing here anyway. Stuart

Wow, this complex.... Thank you. I will try that.
No, don't! There is an easier way.
(...) This is the point at which you are forced to move away from OO thinking.
This seems to be worth clearing a little bit. I usually read people saying that this kind of misundestanding is a confusion with object oriented background, when actually I believe it is not. Magicloud's assumption are all correct, in the Haskell way of thinking. Classes do behave the way he thinks it does. The problem was only that you can't (without existential quantification) build lists of elements with diferent types for each element -- as you also can't do in languages like C++. The way to achieve that in C++ is to use a list of pointers, while in Haskell you can use existential quantification. (Confusion with OO is less of a problem than people use to think it is. I've already been told that something I wanted was OO specific, and I later realized what I needed is available in Haskell and is called associated type, as in type families.) Best, Maurício

Wordy (and yet technically accurate) names aside, isn't this basically the same thing, except that you must pass the dictionary around by hand? What is the advantage of doing the dictionary passing manually, other than being able to avoid the scoping issue (that requires case) and the slightly odd syntax? I'm not saying you're wrong or anything, I'm just curious on your opinion. To expand your example, would you suggest something like: data Widget = Widget { widgetRun :: IO () } data Label = Label (String -> IO ()) data Button = Button (IO ()) labelToWidget = Widget runLabel buttonToWidget = Widget runButton widgetList :: [(Integer, Integer, Widget)] widgetList = [labelToWidget myLabel, buttonToWidget myButton] ? Regarding downcasting, you'd have to use Data.Dynamic or Data.Typeable right? -Ross On Jul 3, 2009, at 3:08 AM, Luke Palmer wrote:
On Thu, Jul 2, 2009 at 8:32 PM, Magicloud Magiclouds
wrote: Wow, this complex.... Thank you. I will try that.
No, don't! There is an easier way.
Don't use a class, just use a record.
I would translate your class as:
data Widget = Widget { widgetRun :: IO () }
If you need more capabilities, add them as fields in this record. There is no need for typeclasses here.
Keep in mind that with this solution *and* with the ExistentialQuantification solution, there is no possibility of downcasting. I.e. if you were planning on making a GraphicalWidget subclass, and them somewhere seeing if a a Widget is actually a GraphicalWidget, you will be disappointed. The solution in this case is to redesign your software not to need downcasting. This is the point at which you are forced to move away from OO thinking.
Luke
You have a couple problems here.
The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic.
The second is that it looks like you probably want a heterogeneous
widgets -- that is, possibly different types of widget as long as
conform to Widget. To do this you'll need ExistentialQuantification (or GADTs I guess?).
For example:
{-# LANGUAGE ExistentialQuantification #-}
class Widget w where widgetRun :: w -> IO ()
data SomeWidget = forall w. Widget w => SomeWidget w
widgetList :: [(Integer, Integer, SomeWidget)] widgetList = []
main = mapM aux widgetList aux (x, y, sw) = case sw of SomeWidget w -> widgetRun w
Note that the type variable for widgetList 'w' has disappeared. Before, with the type variable 'w', all elements of the widgetList had to be of
type (lists being homogeneous). By wrapping up the type variable 'w' inside SomeWidget, you can now have whatever types of widgets in that SomeWidget, e.g.
data Button = Button (IO ()) instance Widget Button where widgetRun = ...
data Label = Label (String -> IO ()) instance Widget Label where widgetRun = ...
widgetList:: [(Integer, Integer, SomeWidget)] widgetList = [ SomeWidget (Button $ putStrLn "ding!") , SomeWidget (Label $ putStrLn . ("entered: " ++)) ]
Before, without existential quantification, you had to have all
On Fri, Jul 3, 2009 at 12:24 PM, Ross Mellgren
wrote: list of they all the same the same type of widget (e.g. all Button or all Label)
Hope this makes it more clear.
-Ross
On Jul 3, 2009, at 12:00 AM, Magicloud Magiclouds wrote:
Hi, I thought "class" was for this purpose. But it turns out not. Code as following could not compiled.
1 main = do 2 mapM_ (\(x, y, widget) -> do 3 a <- widgetRun widget 4 putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) => [(Integer, Integer, w)] 8 widgetList = [] 9 10 class Widget w where 11 widgetRun :: w -> IO () --- % ghc --make tmp/test.hs [1 of 1] Compiling Main ( tmp/test.hs, /tmp/Main.o )
tmp/test.hs:3:16: Ambiguous type variable `t' in the constraint: `Widget t' arising from a use of `widgetRun' at tmp/test.hs: 3:16-31 Probable fix: add a type signature that fixes these type variable(s) -- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 竹密岂妨流水过 山高哪阻野云飞 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2009/7/3 Ross Mellgren
Wordy (and yet technically accurate) names aside, isn't this basically the same thing, except that you must pass the dictionary around by hand?
A SomeWidget is defined as "any object which has a Widget dictionary". It's still an object; the link from it to its dictionary is implicit. But since you have no other qualifiers on that object, nothing can be determined from it but its dictionary. Why not just junk the indirection and make the object equal to its dictionary. This is a different story if you a class like: class Split a where split :: a -> (a,a) join :: a -> a -> a data SomeSplit = forall a. Split a => SomeSplit a Here a SomeSplit can be split into two SomeSplits, but two SomeSplits can't be joined into one. Two join two of these things, you must have split them off a common ancestor.
What is the advantage of doing the dictionary passing manually, other than being able to avoid the scoping issue (that requires case) and the slightly odd syntax?
The fact that it's exactly the same, except for the scoping issue and the slightly odd syntax. You're not saving any parameter passing.
To expand your example, would you suggest something like:
data Widget = Widget { widgetRun :: IO () }
data Label = Label (String -> IO ()) data Button = Button (IO ())
labelToWidget = Widget runLabel buttonToWidget = Widget runButton
widgetList :: [(Integer, Integer, Widget)] widgetList = [labelToWidget myLabel, buttonToWidget myButton]
Yeah sure, something like that. Except, concretely, I don't see how a Label is a String -> IO (). Is that a setter function for its text? How is a Widget going to use that. I guess unless a "label widget" passed *you* a label when you create it. I'd say the other option in this paradigm is a MVar. But I digress... Luke

Hello Magicloud,
I thought "class" was for this purpose. But it turns out not.
http://haskell.org/haskellwiki/OOP_vs_type_classes -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (6)
-
Bulat Ziganshin
-
Luke Palmer
-
Magicloud Magiclouds
-
Maurício
-
Ross Mellgren
-
Stuart Cook