
From: Johan Tibell
(The OOP people, of course, just don't bother trying. They use typecasts everywhere...)
Do associated types solve this? Or are there still problems?
Duncan showed me a definition using associated types, which I have unfortunately forgotten.
Yes, associated types (or fundeps) solve this problem. This problem of container types is one of the motivating examples behind both extensions. I think the real problem we have with container classes has a lot more to do with what we would use them for. That is, Haskell already has Monoid, Foldable and Traversable. These three (especially Foldable) cover nearly everything OOP programmers would expect out of generic container operations. What's missing are classes for specific data types. That is, a Map/Dict interface, a Queue interface, and a Heap interface (probably others too, but these are the first that come to mind). But the standard Data.Map and List (for a queue) seem good enough for most people, so there seems to be a lot of inertia to overcome for these to be popular. John

On 8 February 2011 09:57, John Lato
I think the real problem we have with container classes has a lot more to do with what we would use them for. That is, Haskell already has Monoid, Foldable and Traversable. These three (especially Foldable) cover nearly everything OOP programmers would expect out of generic container operations.
That was what my rewrite was going to be using. The problem, however, is two-fold: * Dealing with types of kind * vs kind * -> * * Dealing with types of kind * -> * that have a restriction on the type parameter (e.g. Set). I was basing my approach on Ganesh's rmonad [1] library whilst taking into account the Functor => Applicative => Monad hierarchy when re-defining the classes, but the approach was very quickly becoming unwieldy. [1]: http://hackage.haskell.org/package/rmonad -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Mon, Feb 7, 2011 at 11:30 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 8 February 2011 09:57, John Lato
wrote: I think the real problem we have with container classes has a lot more to do with what we would use them for. That is, Haskell already has Monoid, Foldable and Traversable. These three (especially Foldable) cover nearly everything OOP programmers would expect out of generic container operations.
That was what my rewrite was going to be using. The problem, however, is two-fold:
* Dealing with types of kind * vs kind * -> *
* Dealing with types of kind * -> * that have a restriction on the type parameter (e.g. Set).
I was basing my approach on Ganesh's rmonad [1] library whilst taking into account the Functor => Applicative => Monad hierarchy when re-defining the classes, but the approach was very quickly becoming unwieldy.
I think the Functor => Applicative => Monad hierarchy should be orthogonal to container design. Although many containers form useful monads, those monads can have very different behavior (e.g. List and Set). Therefore very few (if any) algorithms can both be usefully polymorphic with respect to the container instance and also take advantage of the monadic structure. For those algorithms this is useful, adding an extra Monad to the context is entirely appropriate. Probably more importantly, what users want from a container is often not what the monad provides. Although the List monad is very elegant, I usually find the semantics of ZipList more useful. This leads me to believe that getting "singleton" and "<*>" from a class other than Applicative is the correct approach. Functor is generally better-suited to containers, except for types of kind * that aren't functors. I would suggest there's a better approach than the rmonad machinery, perhaps something like this:
class Container c where type Elem c :: *
class (Container cIn, Container cOut) => CMap cIn cOut where cmap :: (Elem cIn -> Elem cOut) -> cIn -> cOut
instance (a ~ Elem (c a), b ~ Elem (c b), Functor c, Container (c a), Container (c b)) => CMap (c a) (c b) where cmap = fmap
Now we have the same operation which fmap provides, only we can define it for any container type. Better, we have an instance which is suitable for all Functor instances, so we need only write instances for containers of kind * (e.g. ByteString). An annoyance with this approach is that the output type of cmap (c b) can't be determined from the input function, so it's sometimes necessary to add type annotations. I think this can be solved by using bidirectional fundeps instead of associated types though. If you design container classes so that the element type is part of the class instance, restrictions aren't a problem. It's only when you try to accommodate Functor etc. that workarounds such as rmonad become necessary. John

On 8 February 2011 23:25, John Lato
class Container c where type Elem c :: *
class (Container cIn, Container cOut) => CMap cIn cOut where cmap :: (Elem cIn -> Elem cOut) -> cIn -> cOut
instance (a ~ Elem (c a), b ~ Elem (c b), Functor c, Container (c a), Container (c b)) => CMap (c a) (c b) where cmap = fmap
I'm not sure if that will work for types like Set, as you're not explicitly bringing the constraint in. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Tue, Feb 8, 2011 at 12:33 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 8 February 2011 23:25, John Lato
wrote: class Container c where type Elem c :: *
class (Container cIn, Container cOut) => CMap cIn cOut where cmap :: (Elem cIn -> Elem cOut) -> cIn -> cOut
instance (a ~ Elem (c a), b ~ Elem (c b), Functor c, Container (c a), Container (c b)) => CMap (c a) (c b) where cmap = fmap
I'm not sure if that will work for types like Set, as you're not explicitly bringing the constraint in.
It won't work for Set, but Set's not a functor. In this case just write this instance instead:
instance (Ord a, Ord b) => CMap (Set a) (Set b) where cmap = Set.map
John

On Mon, Feb 7, 2011 at 11:57 PM, John Lato
I think the real problem we have with container classes has a lot more to do with what we would use them for. That is, Haskell already has Monoid, Foldable and Traversable. These three (especially Foldable) cover nearly everything OOP programmers would expect out of generic container operations.
Unfortunately using e.g. Foldable hurts performance a lot. We need to look into inlining and specialization and move some functions (e.g. foldl') into the type class if we want acceptable performance.
What's missing are classes for specific data types. That is, a Map/Dict interface, a Queue interface, and a Heap interface (probably others too, but these are the first that come to mind). But the standard Data.Map and List (for a queue) seem good enough for most people, so there seems to be a lot of inertia to overcome for these to be popular.
I think the missing piece to make this abstraction worthwhile is a second Map/Dict type worth using. Then there's a point in abstracting over which type is actually used. In most OOP languages the two map types are sorted and hashed maps. Johan
participants (3)
-
Ivan Lazar Miljenovic
-
Johan Tibell
-
John Lato