
I think left-biased (= singly linked) lists are much overrated in Haskell coding (and teaching). The language (syntax and Prelude) makes it just too easy to use them, and old habits (from LISP) die hard. Sure, lists serve a purpose: * they model (infinite, lazy) streams, used in the producer/transformer/consumer pattern * they are an algebraic data type, so you can use them to teach recursion ((co-)induction); but more often, lists are (mis-)used when actually * you want some efficiently index-able and concat-able sequence type * or you don't need the indexing, just membership, so you actually want Data.Set (disregarding strictness and unwanted Ord instances for the moment). It is an empirical law that in 90 percent of the cases where a computer science student says "list" he means "set". * you avoid/forget to tell your students about algebraic data types in general. Hypothetically now ... We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)? Of course some "minor details" would need to be worked out, like what methods should go in the hypothetical "class IsList" (is is Foldable?) and what to do about pattern matching (perhaps we don't need it?) IIRC there was a time when list comprehension would actually mean monad comprehension (when there was no "do" notation) but that's not what I'm getting at here. Or is it? Do we have a "Haskell museum" of ideas from the past? Best - J.W.

On Mon, 6 Sep 2010, Johannes Waldmann wrote:
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
My favorite solution would be to throw away special list syntax and list comprehensions at all. Then lists and sets are on the same level of compiler support. If find 1:2:3:4:5:[] a perfect way to write lists. Analogously to this we could have an infix operator that is overloaded with (:) for lists and Set.insert for sets.
Of course some "minor details" would need to be worked out, like what methods should go in the hypothetical "class IsList" (is is Foldable?) and what to do about pattern matching (perhaps we don't need it?)
View patterns?
IIRC there was a time when list comprehension would actually mean monad comprehension (when there was no "do" notation) but that's not what I'm getting at here. Or is it? Do we have a "Haskell museum" of ideas from the past?
I think the future ideas collected at the old Hawiki would serve as such museum. Unfortunately Hawiki is gone. I wonder whether I can easily get a dump of HaskellWiki in order to prevent it from the same destiny.

On 06/09/10 11:23, Johannes Waldmann wrote:
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
I would have thought you have two obvious choices for the type-class (things like folding are irrelevant to overloading list literals): class IsList f where fromList :: [a] -> f a or: class IsList f where cons :: a -> f a -> f a empty :: f a I'd go for the first, as I'd imagine you are only overloading the [a,b,c] form, not the a:b:c:[] form, and the first reflects this better. Both of these could be used to convert a list literal into a list-like type (e.g. Sequence). But neither of them would be useful for sets or maps, because the classes lack an Ord constraint on the type a -- maybe this makes overloaded list literals fairly limited in utility. Thanks, Neil.

Am Montag, den 06.09.2010, 11:47 +0100 schrieb Neil Brown:
I would have thought you have two obvious choices for the type-class (things like folding are irrelevant to overloading list literals):
class IsList f where fromList :: [a] -> f a
or:
class IsList f where cons :: a -> f a -> f a empty :: f a
We should definitely get rid of these Is* class identifiers like IsString and IsList. We also don’t have IsNum, IsMonad, etc. Best wishes, Wolfgang

Wolfgang,
We should definitely get rid of these Is* class identifiers like IsString and IsList. We also don’t have IsNum, IsMonad, etc.
I see your point. For strings, however, there was of course never the possibility to dub the class String as that name is already taken by the type synonym. In general, it is kind of unfortunate that type classes and type constructors share a namespace, even though there is no way to ever mix them up. Cheers, Stefan

On Mon, 6 Sep 2010, Stefan Holdermans wrote:
Wolfgang,
We should definitely get rid of these Is* class identifiers like IsString and IsList. We also don’t have IsNum, IsMonad, etc.
I see your point. For strings, however, there was of course never the possibility to dub the class String as that name is already taken by the type synonym.
StringLike would have been an alternative.

On Sep 6, 2010, at 1:47 PM, Stefan Holdermans wrote:
In general, it is kind of unfortunate that type classes and type constructors share a namespace, even though there is no way to ever mix them up.
Class and type names mix in im- and export lists. IIRC, this is the reason for putting them in a common name space. -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Hello Stefan, Monday, September 6, 2010, 3:47:11 PM, you wrote:
In general, it is kind of unfortunate that type classes and type constructors share a namespace, even though there is no way to ever mix them up.
btw, i also had proposal to automatically convert typeclasses used in type declarations into constraints, so that: putStr :: StringLike -> IO () treated as putStr :: StringLike s => s -> IO () and length :: ListLike a -> Int treated as length :: ListLike (c a) => c a -> Int Together with proposals i mentioned previously, it will allow to treat existing code dealing with lists/strings as generic code working with any sequential container type -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat,
btw, i also had proposal to automatically convert typeclasses used in type declarations into constraints, [...]
Together with proposals i mentioned previously, it will allow to treat existing code dealing with lists/strings as generic code working with any sequential container type
I see. That's a nice proposal, but somehow I'm a bit worried about readability of code. IMHO, readability is still one of Haskell's main assets and I wouldn't like to see it degrade (further). Cheers, Stefan

Am Montag, den 06.09.2010, 19:38 +0400 schrieb Bulat Ziganshin:
btw, i also had proposal to automatically convert typeclasses used in type declarations into constraints, so that:
putStr :: StringLike -> IO ()
treated as
putStr :: StringLike s => s -> IO ()
This blurs the distinction between classes and types, which are two fundamentally different concepts in Haskell. In addition, it works only for special cases. I would like the language to be simple. Alas, more and more sugar is added to Haskell, which makes it unnecessarily complicated. Best wishes, Wolfgang

Hi,
actually this idea generalizes quite nicely. Details and examples are
available in Section 3 of "Language and Program Design for Functional
Dependencies", available at
http://web.cecs.pdx.edu/~mpj/pubs/fundeps-design.html
-Iavor
On Mon, Sep 6, 2010 at 3:58 PM, Wolfgang Jeltsch
Am Montag, den 06.09.2010, 19:38 +0400 schrieb Bulat Ziganshin:
btw, i also had proposal to automatically convert typeclasses used in type declarations into constraints, so that:
putStr :: StringLike -> IO ()
treated as
putStr :: StringLike s => s -> IO ()
This blurs the distinction between classes and types, which are two fundamentally different concepts in Haskell. In addition, it works only for special cases. I would like the language to be simple. Alas, more and more sugar is added to Haskell, which makes it unnecessarily complicated.
Best wishes, Wolfgang
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Sep 6, 2010 at 12:47 PM, Neil Brown
On 06/09/10 11:23, Johannes Waldmann wrote:
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
I would have thought you have two obvious choices for the type-class (things like folding are irrelevant to overloading list literals):
class IsList f where fromList :: [a] -> f a
or:
class IsList f where cons :: a -> f a -> f a empty :: f a
I'd go for the first, as I'd imagine you are only overloading the [a,b,c] form, not the a:b:c:[] form, and the first reflects this better. Both of these could be used to convert a list literal into a list-like type (e.g. Sequence). But neither of them would be useful for sets or maps, because the classes lack an Ord constraint on the type a -- maybe this makes overloaded list literals fairly limited in utility.
I endorse the idea of a class along the lines of the first example. That takes care of convenient syntax for literals; view patterns can give you the other end, pattern matching*. The fact that this doesn't work for Sets and the like is indeed troublesome, but I think you can solve it: class IsListLikeThingamabob f where type ElemOf f fromList :: [ElemOf f] -> f then you can do: instance Ord a => IsListLikeThingamabob (S.Set a) where type ElemOf (S.Set a) = a fromList = S.fromList and that way you can also use it for *-kinded types like ByteString, if for whatever reason you might want to. I think the aim here should be just to gain access to the convenient list syntax for use with other types -- a fully generalized interface for collections of all shapes and sizes is out of scope, and _hard_. (But Ivan Miljenovic seems to be working on it.) * Especially if, as discussed on the wiki[1], view patterns also get upgraded to hook into a type class: data View a where type ViewOf a view :: a -> ViewOf a where defining an instance would allow you to omit the name of the viewing function, defaulting to 'view' instead. So if you define ViewOf (MyContainer a) as [a], you could match using: foo (-> []) = something foo (-> x:xs) = something else (I believe the main holdup wrt this is indecision over whether to use a plain MPTC, or a fundep / associated type in one direction, or one in the other. The version above looks clearly superior to me, but I don't want to derail the thread further. If someone else does, fork it. :) [1] http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
Thanks,
Neil. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

Hello Johannes, Monday, September 6, 2010, 2:23:35 PM, you wrote: i had such idea several years ago and proposed to name class ListLike. this class was finally implemented by John Goerzen and it does everything we can w/o changing language the main thing about literals is that they need to be recognized also at left side of equations, so that length (s:xs) = 1 + length xs length [] = 0 will work for ByteStrings and arrays like it work for list. if it will be implemented, then most programs manipulating on lists/strings, can be converted to more efficient ones simply by replacing imports Haskell 1.0 views may be the way to go, virtually converting other containers to lists, back and forth. of course, only if these virtual conversions will be optimized away by smart compiler
I think left-biased (= singly linked) lists are much overrated in Haskell coding (and teaching).
The language (syntax and Prelude) makes it just too easy to use them, and old habits (from LISP) die hard.
Sure, lists serve a purpose: * they model (infinite, lazy) streams, used in the producer/transformer/consumer pattern * they are an algebraic data type, so you can use them to teach recursion ((co-)induction);
but more often, lists are (mis-)used when actually * you want some efficiently index-able and concat-able sequence type * or you don't need the indexing, just membership, so you actually want Data.Set (disregarding strictness and unwanted Ord instances for the moment). It is an empirical law that in 90 percent of the cases where a computer science student says "list" he means "set". * you avoid/forget to tell your students about algebraic data types in general.
Hypothetically now ...
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
Of course some "minor details" would need to be worked out, like what methods should go in the hypothetical "class IsList" (is is Foldable?) and what to do about pattern matching (perhaps we don't need it?)
IIRC there was a time when list comprehension would actually mean monad comprehension (when there was no "do" notation) but that's not what I'm getting at here. Or is it? Do we have a "Haskell museum" of ideas from the past?
Best - J.W.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sep 6, 2010, at 12:23 PM, Johannes Waldmann wrote:
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
As lists of some type A represent the free monoid over A, what if [x,y,z] would be syntactic sugar for mconcat (map point (x:y:z:[])) with class Pointed p where point :: a -> p a Then list literals could be used for every pointed monoid. Note that this only considers list literals. The (:) and [] constructors would not be overloaded. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Hello Johannes, Monday, September 6, 2010, 2:23:35 PM, you wrote:
so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
i'vwe found my own proposal of such type: http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2010/9/6 Bulat Ziganshin
Hello Johannes,
Monday, September 6, 2010, 2:23:35 PM, you wrote:
so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
i'vwe found my own proposal of such type: http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html
Will Data.Map with its' empty, insert, findMin, etc, "methods" conform to your proposed type? I don't think so and I thought twice. ;)

Hello Serguey, Monday, September 6, 2010, 7:57:46 PM, you wrote:
http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html
Will Data.Map with its' empty, insert, findMin, etc, "methods" conform to your proposed type?
but Data.Map isn't sequential container. instead, it maps arbitrary keys to values -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2010/9/6 Bulat Ziganshin
Hello Serguey, Monday, September 6, 2010, 7:57:46 PM, you wrote:
http://www.mail-archive.com/haskell-cafe@haskell.org/msg15656.html Will Data.Map with its' empty, insert, findMin, etc, "methods" conform to your proposed type? but Data.Map isn't sequential container. instead, it maps arbitrary keys to values
That situation reminds me situation with Set Monad instance. ;) Basically, you - and others, - propose to add another class isomorphic to already present lists. I think, most benefits of that class can be achieved by using list conversion and RULE pragma.

Hello Serguey, Monday, September 6, 2010, 8:16:03 PM, you wrote:
Basically, you - and others, - propose to add another class isomorphic to already present lists. I think, most benefits of that class can be achieved by using list conversion and RULE pragma.
what i propose should allow to convert algorithm dealing with strings into algorithm dealing with ByteStrings, simply by changing import statement it's a cute goal - keep Haskell strings easy of use but add ByteString performance -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2010/9/6 Bulat Ziganshin
Hello Serguey,
Monday, September 6, 2010, 8:16:03 PM, you wrote:
Basically, you - and others, - propose to add another class isomorphic to already present lists. I think, most benefits of that class can be achieved by using list conversion and RULE pragma. what i propose should allow to convert algorithm dealing with strings into algorithm dealing with ByteStrings, simply by changing import statement
View patterns?.. Also, I think that some general optimization that can fold computations together (like supercompilation) will certainly help here.
it's a cute goal - keep Haskell strings easy of use but add ByteString performance
Completely agree, this is a noble goal. But ByteStrings aren't polymorphic. So they cannot satisfy your class.

On Mon, 2010-09-06 at 10:23 +0000, Johannes Waldmann wrote:
We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)?
Of course some "minor details" would need to be worked out, like what methods should go in the hypothetical "class IsList" (is is Foldable?) and what to do about pattern matching (perhaps we don't need it?)
Foldable is not necessary a good choice. Neither ByteString nor Text is Foldable. It would make hard to write methods like: checkMagicKey :: ByteString -> Bool checkMagicKey (0x85:0x86:_) = True checkMagicKey _ = False or checkFoo :: Text -> Bool checkFoo "Foo" = True checkFoo _ = False
IIRC there was a time when list comprehension would actually mean monad comprehension (when there was no "do" notation) but that's not what I'm getting at here. Or is it? Do we have a "Haskell museum" of ideas from the past?
Best - J.W.
I guess the laziness and view patterns are sufficient: checkMagicKey :: ByteString -> Bool checkMagicKey (unpack -> 0x85:0x86:_) = True checkMagicKey _ = False checkFoo :: Text -> Bool checkFoo (unpack -> "Foo") = True checkFoo _ = False The problems: - In teaching list are useful because they are simple. View patterns are not. Even if view patterns were standard it could be considered too complicated to teach. - They introduce nothing more then is already achievable as it is possible to write checkFoo x = case unpack x of "Foo" -> ... _ -> ... or checkFoo x | unpack x == "Foo" = ... | otherwise = ... - I may be wrong but they require the recomputation on each call of unpack I guess that maybe active patterns should be considered to be imported from F#. I'm not quite sure about syntax and maybe they are too "logic" like. PS. data FooBar a = Foo | Bar deriving Show class IsString (FooBar Char) where toString _ = Foo class IsList FooBar where toList _ = Bar show ("1234" :: FooBar Char) == ???

On Mon, Sep 6, 2010 at 8:52 PM, Maciej Piechotka
PS.
data FooBar a = Foo | Bar deriving Show
class IsString (FooBar Char) where toString _ = Foo
class IsList FooBar where toList _ = Bar
show ("1234" :: FooBar Char) == ???
Foo -- Work is punishment for failing to procrastinate effectively.
participants (11)
-
Bulat Ziganshin
-
Gábor Lehel
-
Henning Thielemann
-
Iavor Diatchki
-
Johannes Waldmann
-
Maciej Piechotka
-
Neil Brown
-
Sebastian Fischer
-
Serguey Zefirov
-
Stefan Holdermans
-
Wolfgang Jeltsch