Is there already a list class?

Hello. Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: .. This might be used in Data.Set, Data.Map class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e I'd like to help implementing/ writing it. Do you consider this beeing a useful enhancement? Cheers Marc Weber

Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: ..
This might be used in Data.Set, Data.Map
class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e
I'd like to help implementing/ writing it.
Do you consider this beeing a useful enhancement?
I was looking for such a class just yesterday. I wanted a difference list over LazyByteString, and it seemed wrong just to rewrite Don Stewart's DList for byte strings without first having a list class. I would also like to help implement it.

I've written some classes for this type of functionality as well. I think what I've written can be generalized, so I'd like to participate if folks decide to pursue this.
Seth Kurtzberg
On Wed, 10 Jan 2007 11:23:20 +1000
"Matthew Brecknell"
Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: ..
This might be used in Data.Set, Data.Map
class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e
I'd like to help implementing/ writing it.
Do you consider this beeing a useful enhancement?
I was looking for such a class just yesterday. I wanted a difference list over LazyByteString, and it seemed wrong just to rewrite Don Stewart's DList for byte strings without first having a list class.
I would also like to help implement it.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Wed, Jan 10, 2007 at 02:52:52AM +0100, Marc Weber wrote:
Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: ..
This might be used in Data.Set, Data.Map
class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e
I'd like to help implementing/ writing it.
Do you consider this beeing a useful enhancement?
This is a major part of my wishlist for a new set of libraries in the post-Haskell' era (or perhaps for Haskell'). Rewriting the prelude (which is essentially what you're suggesting) and standard libraries is part of the haskell' effort, and most people I have talked with would prefer to reduce its size as far as possible. Alas, I don't forsee having any time for this in the forseeable future, but I've got lots of ideas. I think you'd want a higher-kinded list type rather than a MPTC: class List l where cons :: e -> l e -> l e -- you can't make a constructor a member of a class head :: l e -> e null :: l e -> Bool empty :: l e ... Also on the wishlist would be to rename fmap to map, and add an instance instance List l => Functor l where map :: (a -> b) -> l a -> l b map f l | null l = empty | otherwise = f (head l) `cons` tail l Ideally, I'd like the prelude contain almost no functions that are not defined within a class, so that we could apply all the standard prelude functions to any reasonable data type we wish. In my opinion, the API provided by modules like Data.Map and Data.FastPackedString which we are forced to import qualified because they conflict with the Prelude are an abomination forced upon us by the short-sighted design of the Prelude. The only argument for not putting these functions into classes is that it would make error messages harder for students. There have been multiple suggestions for alleviating that, ranging from better compiler error messages (pretty hard) to a special "easy" prelude. The latter seems like a better idea. There are some difficulties, however, such as the trickiness that some data structures (which you'd like to use the same interface) have constraints, such as they require that the stored type be in class Ord. These issues are a real pain, and I know other people have thought long and hard about it, but I haven't. -- David Roundy Department of Physics Oregon State University

On Tue, Jan 09, 2007 at 05:54:11PM -0800, David Roundy wrote:
I think you'd want a higher-kinded list type rather than a MPTC:
class List l where cons :: e -> l e -> l e -- you can't make a constructor a member of a class head :: l e -> e null :: l e -> Bool empty :: l e ...
Okay, this was stupid of me. As Spencer points out, we wouldn't actually want a list type with kind * -> *, because we'd want to support specialized lists like Data.Bytestring. So we'd want something more like
class List l e, l -> e where cons :: e -> l -> l head :: l -> e null :: l -> Bool empty :: l ...
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...) -- David Roundy http://www.darcs.net

I suggest you have a look a the classes for collections that I've been
working on.
It's an attempt at unifying all collection types in a single framework
of classes.
darcs repository:
http://darcs.haskell.org/packages/collections
On 1/10/07, David Roundy
On Tue, Jan 09, 2007 at 05:54:11PM -0800, David Roundy wrote:
I think you'd want a higher-kinded list type rather than a MPTC:
class List l where cons :: e -> l e -> l e -- you can't make a constructor a member of a class head :: l e -> e null :: l e -> Bool empty :: l e ...
Okay, this was stupid of me. As Spencer points out, we wouldn't actually want a list type with kind * -> *, because we'd want to support specialized lists like Data.Bytestring. So we'd want something more like
class List l e, l -> e where cons :: e -> l -> l head :: l -> e null :: l -> Bool empty :: l ...
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...) -- David Roundy http://www.darcs.net _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Jan 10, 2007, at 3:25 AM, Jean-Philippe Bernardy wrote:
I suggest you have a look a the classes for collections that I've been working on. It's an attempt at unifying all collection types in a single framework of classes.
darcs repository:
How does this library compare to Edison? Cheers, Spencer Janssen

On 1/10/07, Spencer Janssen
On Jan 10, 2007, at 3:25 AM, Jean-Philippe Bernardy wrote:
I suggest you have a look a the classes for collections that I've been working on. It's an attempt at unifying all collection types in a single framework of classes.
darcs repository:
How does this library compare to Edison?
The collections package is intended as an evolution from the collection types in the package rather than a radically different design. In other words, it's easier to move to the collection packages than to edison. Another advantage is that every type is in the same "hierarchy" of classes (no separate class for associative collections). It also makes heavy usage of MTPC+fundeps, I suspect in a way very close to what Robert plans to do for edison. On the other hand, there are more types in the edison library. Robert: if that is actually the direction where you want to move for edison, I'd suggest to merge the two packages. Here's the link to the wiki page: http://haskell.org/haskellwiki/Library/New_collections Cheers, JP.

On Jan 10, 2007, at 11:12 AM, Jean-Philippe Bernardy wrote:
On 1/10/07, Spencer Janssen
wrote: I suggest you have a look a the classes for collections that I've been working on. It's an attempt at unifying all collection types in a single
On Jan 10, 2007, at 3:25 AM, Jean-Philippe Bernardy wrote: framework
of classes.
darcs repository:
How does this library compare to Edison?
The collections package is intended as an evolution from the collection types in the package rather than a radically different design. In other words, it's easier to move to the collection packages than to edison. Another advantage is that every type is in the same "hierarchy" of classes (no separate class for associative collections). It also makes heavy usage of MTPC+fundeps, I suspect in a way very close to what Robert plans to do for edison. On the other hand, there are more types in the edison library.
Robert: if that is actually the direction where you want to move for edison, I'd suggest to merge the two packages.
Something like this might be feasible for the medium/long-term reorg I have in mind; however, like I said, I'm still trying to work out exactly what I'm aiming for. I have this thought that there should be some principled way to organize these classes based on an underlying mathematical model, but it hasn't quite crystalized in my head yet.
Here's the link to the wiki page: http://haskell.org/haskellwiki/Library/New_collections
Cheers, JP.
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On 2007-01-10, David Roundy
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...)
Huh. I don't understand associated types, and functional dependencies seem fairly transparent, if perhaps low-level to me. -- Aaron Denney -><-

On Wed, Jan 10, 2007 at 09:54:57AM +0000, Aaron Denney wrote:
On 2007-01-10, David Roundy
wrote: (But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...)
Huh. I don't understand associated types, and functional dependencies seem fairly transparent, if perhaps low-level to me.
The trouble is that fundeps *seem* transparent, but they aren't (at least, according to implementors). ATs, once you have heard about them, actually are simple, I believe. It's the restrictions on fundeps to allow termination and decideability that make them confusing... -- David Roundy http://www.darcs.net

I think we should rewrite ByteString and call it WordString.. eg data WordString word = ... type ByteString = WordString Word8 Than the problem would be gone and we would also gain an ByteString implementation for Unicode, right? *smile* But I don't know ByteString that well by now so I might be totally wrong.. Marc

Hello Marc, Wednesday, January 10, 2007, 2:19:08 PM, you wrote:
data WordString word = ... type ByteString = WordString Word8
Than the problem would be gone and we would also gain an ByteString implementation for Unicode, right? *smile*
But I don't know ByteString that well by now so I might be totally wrong..
yes, and it was proposed numerous times. but other parameter-less collection implementations can still exist btw, i've attached my own demo of such class together with example of generic foldr i also have proposed to extend syntax of (:), [] (including pattern matching) in Haskell' to use this class operations instead of be bound to lazy lists -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Wed, Jan 10, 2007 at 12:19:08PM +0100, Marc Weber wrote:
I think we should rewrite ByteString and call it WordString.. eg
data WordString word = ... type ByteString = WordString Word8
Than the problem would be gone and we would also gain an ByteString implementation for Unicode, right? *smile*
But I don't know ByteString that well by now so I might be totally wrong..
WordString a is a good idea, it would be *much* more efficient then [a], *but* it would be nowhere near as efficient as ByteString. WordString Word8 would require 4 or 12 bytes per character - one for a pointer (because you can't unpack a type variable), and optionally 8 more for the Word8 heap object (4 for the tag word, 1 for the Word8#, and 3 for alignment). By contrast, ByteString requires 1 byte per character, and [Word8] requires 12 or 20. (And 64-bit platforms will make it 1/8/24...) Furthermore, as a selfish American, I use the US-ASCII subset of Unicode exclusively, and don't want my ten-gigabyte bytestrings to quadruple in size and sloth. I would much rather see a Data.ByteString.UTF8.

Stefan O'Rear wrote:
WordString a is a good idea, it would be *much* more efficient then [a], *but* it would be nowhere near as efficient as ByteString.
WordString Word8 would require 4 or 12 bytes per character - one for a pointer (because you can't unpack a type variable)
Then it should be StorableString and everything would be peeked and poked into an array of bytes. Full performance would be recovered by automatically specializing and inlining most code.
Furthermore, as a selfish American, I use the US-ASCII subset of Unicode exclusively, and don't want my ten-gigabyte bytestrings to quadruple in size and sloth. I would much rather see a Data.ByteString.UTF8.
On the other hand, as a selfish German, I use these annoying umlauts, which means I want this coding issue solved once and for all. Why can't we have polymorphic StorableString (spezialized to Word8, Word16 and Char), tagged with a (phantom?) type that denotes its encoding? A typesafe interface to iconv would be a good thing, too. -Udo -- "Don't you know that alcohol for a young man is nothing but slow poison?" "Slow poison, eh? Well, I'm not in any hurry." -- found at http://c2.com/cgi-bin/wiki?SlowPoison

Hello David, Wednesday, January 10, 2007, 5:35:03 AM, you wrote:
class List l e, l -> e where
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...)
well, it is pretty studied design space, you can look the chapter about fundeps in ghc 6.6 manual which describes various solutions for containers class problem generally, we need either FD (which is not a part of Haskell') or AT (which is supported only by GHC HEAD) about existing implementations: 1) Stringable class in fps-soc project. it is aimed to generalize interface of String and ButeString 2) numerous classes in Collections [2] and Edison [3] libraries [1] http://darcs.haskell.org/SoC/fps-soc [2] http://darcs.haskell.org/packages/collections [3] http://www.eecs.tufts.edu/~rdocki01/projects/edison-1.2rc4-source.tar.gz -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Jan 10, 2007, at 7:27 AM, Bulat Ziganshin wrote:
Hello David,
Wednesday, January 10, 2007, 5:35:03 AM, you wrote:
class List l e, l -> e where
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...)
well, it is pretty studied design space, you can look the chapter about fundeps in ghc 6.6 manual which describes various solutions for containers class problem
generally, we need either FD (which is not a part of Haskell') or AT (which is supported only by GHC HEAD)
about existing implementations:
1) Stringable class in fps-soc project. it is aimed to generalize interface of String and ButeString
2) numerous classes in Collections [2] and Edison [3] libraries
[1] http://darcs.haskell.org/SoC/fps-soc [2] http://darcs.haskell.org/packages/collections [3] http://www.eecs.tufts.edu/~rdocki01/projects/edison-1.2rc4- source.tar.gz
FYI, this is not the latest release of Edison. The latest release is available from: http://www.eecs.tufts.edu/~rdocki01/edison.html
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On Wed, Jan 10, 2007 at 03:27:40PM +0300, Bulat Ziganshin wrote:
Hello David,
Hi Bulat,
Wednesday, January 10, 2007, 5:35:03 AM, you wrote:
class List l e, l -> e where
(But I don't like functional dependencies, because they confuse me, and hope that associated types end up making it into Haskell'...)
well, it is pretty studied design space, you can look the chapter about fundeps in ghc 6.6 manual which describes various solutions for containers class problem
I understand the idea of fundeps, but not their limitations--and every time I've tried to actually use them (admittedly, always for something harder than this) those limitations have bitten me. And the answer always seems to be that the code is correct, but there are reasons (involving termination or decidability) that I don't understand, why the compiler can't accept my code. From what I've heard from Manuel, with AT (and indexed types in general) the restrictions are identical, but are far easier to explain to a naive programmer such as myself.
generally, we need either FD (which is not a part of Haskell') or AT (which is supported only by GHC HEAD)
Yes, and I'm rooting for AT. Since no two implementations support the *same* FD, the only issues are that AT is only supported by ghc HEAD rather than also being supported by a released ghc, and also that no existing code uses AT. But to me, the ease of understanding absolutely outweighs those issues, and it seems like a language feature that's easy for programmers to reason about should also be easier for implementors to get right. And I don't know if you're aware of this, but the current plans are for ghc to switch to implementing fundeps via a translation into AT, which apparently will significantly simplify ghc's code. Admittedly, this is partly just because the fundeps implementation predates system fc, and doesn't take advantage of it as AT does. -- David Roundy http://www.darcs.net

On Jan 9, 2007, at 7:52 PM, Marc Weber wrote:
Hello.
Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: ..
Note that this approach isn't quite flexible enough. Your example forces the container type to have kind * -> *, and therefore can't support certain specialized containers like ByteString. There is a class like this in the Edison library (http:// www.eecs.tufts.edu/~rdocki01/edison.html), it is called Seq (Haddocks: http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data- Edison-Seq.html). However, it suffers the same kind flexibility issues as your List class. Other classes in Edison take a MPTC +fundep approach and I'm not sure why Seq doesn't. Can you comment on this, Rob?
This might be used in Data.Set, Data.Map
class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e
This is subsumed by other Edison functionality.
I'd like to help implementing/ writing it.
Do you consider this beeing a useful enhancement?
Oh yes, but let's avoid reinventing the wheel if at all possible. Spencer Janssen

On Jan 9, 2007, at 9:12 PM, Spencer Janssen wrote:
On Jan 9, 2007, at 7:52 PM, Marc Weber wrote:
Hello.
Is here the right place to request a list class? eg class List l e where (:) :: e -> l e -> l e head :: ..
Note that this approach isn't quite flexible enough. Your example forces the container type to have kind * -> *, and therefore can't support certain specialized containers like ByteString.
There is a class like this in the Edison library (http:// www.eecs.tufts.edu/~rdocki01/edison.html), it is called Seq (Haddocks: http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data- Edison-Seq.html). However, it suffers the same kind flexibility issues as your List class. Other classes in Edison take a MPTC +fundep approach and I'm not sure why Seq doesn't. Can you comment on this, Rob?
I consider this mostly a historical artifact. The Edison design dates back to about 1998, before fundeps were available in a Haskell implementation. The Set/Bag and Finite Map classes were designed with MPTC, but no fundeps. The sequence class was nicer because it was more elegant, and played nicer with type inference. In the course of time, Set/Bag and Finite Map classes got fundeps, and became a bit nicer. When I took over maintenance, the typeclass hierarchy was much as it is now. I am personally in favor of the idea of changing the sequence class to the MPTC+fundep approach, for largely the reasons you've mentioned. The downsides are twofold: 1) Functor, Monad, and MonadPlus could no longer be superclasses of Sequence and 2) its a pretty major API change. Despite the downsides, I've become convinced this is the right direction to go, and this change will almost certainly take place sometime in the not too distant future. I'm now finished with some work which was occupying most my attention for the last six months or so. I am also considering a more sweeping API reorganization, where the typeclasses become less monolithic (especially the sequence class), and the non-observable classes go away, but I'm still trying to figure out the most optimal way to restructure things, so this change won't happen for awhile.
This might be used in Data.Set, Data.Map
class StorableAsList l e t where fromList :: l e -> t toList :: t -> l e
This is subsumed by other Edison functionality.
I'd like to help implementing/ writing it.
Do you consider this beeing a useful enhancement?
Oh yes, but let's avoid reinventing the wheel if at all possible.
Spencer Janssen
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Did anything ever come of this discussion? http://www.haskell.org/pipermail/libraries/2007-January/006704.html I found myself writing this the other day to capture the fact that IA5 characters are the building blocks of IA5 strings. Dominic. newtype IA5String = IA5String {unIA5String :: String} newtype IA5Char = IA5Char {unIA5Char :: Char} class List a b | a -> b where nil :: b cons :: a -> b -> b instance List IA5Char IA5String where nil = IA5String [] cons x y = IA5String ((unIA5Char x):(unIA5String y))
participants (12)
-
Aaron Denney
-
Bulat Ziganshin
-
David Roundy
-
Dominic Steinitz
-
Jean-Philippe Bernardy
-
Marc Weber
-
Matthew Brecknell
-
Robert Dockins
-
Seth Kurtzberg
-
Spencer Janssen
-
Stefan O'Rear
-
Udo Stenzel