
GHC Users, I would like to make to the following two proposals: * Eliminate the default grouping close from SQL-like comprehensions * Introduce a GHC extension for list literal overloading OK, let me start with the first proposal. Currently, the SQL-like comprehension notation (both in its list comprehension and monad comprehension variants) features the following five clauses: then f then f by e then group by e then group using f then group by e using f The first two clauses are used for specifying transformations of type [a] -> [a] (or Monad m => m a-> m a for monad comprehensions). The following three clauses are used for specifying transformations of type [a] -> [[a]] (or Monad m, Functor f => m a -> m (f a) for monad comprehensions). See [1] for further details. Note that the third clause does not mention which function is used for grouping. In this case GHC.Exts.groupWith function is used as a default for list comprehensions and the mgroupWith function from the MonadGroup class is used as a default for monad comprehensions. I would like to suggest to remove the third clause for the following reasons: * Currently the syntax is asymmetrical. Note that there is the default case for the 'then group' clause and not for the 'then' clause. * In the current notation it is not clear which grouping function is used in the default case * For many monads including lists it is not clear which function should be selected as a default (e.g., the groupWith function also does sorting and it is not clear to me why this should be the default) * Gets rid of the MonadGroup class. Currently the sole purpose of this class is to introduce a default grouping function for monad comprehensions. * Explicit mention of the grouping function would make monad/list comprehensions much easier to read by making it immediately apparent which function is used for grouping. My second proposal is to introduce the OverloadedLists extension that overloads list literals. See Section 5.2 in [1] for details. Basically the idea is to treat list literals like: [1,2,3] as fromList [1,2,3] where class IsList l where type Item l fromList :: [Item l] -> l In the following I give useful instances of the IsList class. instance IsList [a] where type Item [a] = a fromList = id instance (Ord a) => IsList (Set a) where type Item (Set a) = a fromList = Set.fromList instance (Ord k) => IsList (Map k v) where type Item (Map k v) = (k,v) fromList = Map.fromList instance IsList (IntMap v) where type Item (IntMap v) = (Int,v) fromList = IntMap.fromList instance IsList Text where type Item Text = Char fromList = Text.pack As you can see the extension would allow list literals to be used for sets, maps and integer maps. In addition the suggested OverloadedLists extension would subsume OverloadedStrings extension (see the instance for Text, for example). Having said that, for now, I am not suggesting to remove the OverloadedStrings extension as it appears to be widely used. This extension could also be used for giving data-parallel array literals instead of the special syntax used currently. Unless there is a vocal opposition to the aforementioned two proposals, I would like to implement them in GHC. Both changes appear to be straightforward to implement. Thanks in advance for your feedback. Cheers, George [1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf

What are the defaulting rules for IsList? It needs to be backwards compatible.
-- Lennart (iPhone)
On Sep 30, 2011, at 19:28, George Giorgidze
GHC Users,
I would like to make to the following two proposals: * Eliminate the default grouping close from SQL-like comprehensions * Introduce a GHC extension for list literal overloading
OK, let me start with the first proposal.
Currently, the SQL-like comprehension notation (both in its list comprehension and monad comprehension variants) features the following five clauses:
then f then f by e then group by e then group using f then group by e using f
The first two clauses are used for specifying transformations of type [a] -> [a] (or Monad m => m a-> m a for monad comprehensions). The following three clauses are used for specifying transformations of type [a] -> [[a]] (or Monad m, Functor f => m a -> m (f a) for monad comprehensions). See [1] for further details.
Note that the third clause does not mention which function is used for grouping. In this case GHC.Exts.groupWith function is used as a default for list comprehensions and the mgroupWith function from the MonadGroup class is used as a default for monad comprehensions.
I would like to suggest to remove the third clause for the following reasons: * Currently the syntax is asymmetrical. Note that there is the default case for the 'then group' clause and not for the 'then' clause. * In the current notation it is not clear which grouping function is used in the default case * For many monads including lists it is not clear which function should be selected as a default (e.g., the groupWith function also does sorting and it is not clear to me why this should be the default) * Gets rid of the MonadGroup class. Currently the sole purpose of this class is to introduce a default grouping function for monad comprehensions. * Explicit mention of the grouping function would make monad/list comprehensions much easier to read by making it immediately apparent which function is used for grouping.
My second proposal is to introduce the OverloadedLists extension that overloads list literals. See Section 5.2 in [1] for details.
Basically the idea is to treat list literals like:
[1,2,3]
as
fromList [1,2,3]
where
class IsList l where type Item l fromList :: [Item l] -> l
In the following I give useful instances of the IsList class.
instance IsList [a] where type Item [a] = a fromList = id
instance (Ord a) => IsList (Set a) where type Item (Set a) = a fromList = Set.fromList
instance (Ord k) => IsList (Map k v) where type Item (Map k v) = (k,v) fromList = Map.fromList
instance IsList (IntMap v) where type Item (IntMap v) = (Int,v) fromList = IntMap.fromList
instance IsList Text where type Item Text = Char fromList = Text.pack
As you can see the extension would allow list literals to be used for sets, maps and integer maps. In addition the suggested OverloadedLists extension would subsume OverloadedStrings extension (see the instance for Text, for example). Having said that, for now, I am not suggesting to remove the OverloadedStrings extension as it appears to be widely used.
This extension could also be used for giving data-parallel array literals instead of the special syntax used currently.
Unless there is a vocal opposition to the aforementioned two proposals, I would like to implement them in GHC. Both changes appear to be straightforward to implement.
Thanks in advance for your feedback.
Cheers, George
[1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I like both George's proposals. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of George Giorgidze | Sent: 30 September 2011 18:28 | To: glasgow-haskell-users@haskell.org | Subject: Two Proposals | | GHC Users, | | I would like to make to the following two proposals: | * Eliminate the default grouping close from SQL-like comprehensions | * Introduce a GHC extension for list literal overloading | | OK, let me start with the first proposal. | | Currently, the SQL-like comprehension notation (both in its list comprehension and | monad comprehension variants) features the following five clauses: | | then f | then f by e | then group by e | then group using f | then group by e using f | | The first two clauses are used for specifying transformations of type [a] -> [a] (or | Monad m => m a-> m a for monad comprehensions). The following three clauses are used | for specifying transformations of type [a] -> [[a]] (or Monad m, Functor f => m a -> | m (f a) for monad comprehensions). See [1] for further details. | | Note that the third clause does not mention which function is used for grouping. In | this case GHC.Exts.groupWith function is used as a default for list comprehensions | and the mgroupWith function from the MonadGroup class is used as a default for monad | comprehensions. | | I would like to suggest to remove the third clause for the following reasons: | * Currently the syntax is asymmetrical. Note that there is the default case for the | 'then group' clause and not for the 'then' clause. | * In the current notation it is not clear which grouping function is used in the | default case | * For many monads including lists it is not clear which function should be selected | as a default (e.g., the groupWith function also does sorting and it is not clear to | me why this should be the default) | * Gets rid of the MonadGroup class. Currently the sole purpose of this class is to | introduce a default grouping function for monad comprehensions. | * Explicit mention of the grouping function would make monad/list comprehensions | much easier to read by making it immediately apparent which function is used for | grouping. | | My second proposal is to introduce the OverloadedLists extension that overloads list | literals. See Section 5.2 in [1] for details. | | Basically the idea is to treat list literals like: | | [1,2,3] | | as | | fromList [1,2,3] | | where | | class IsList l where | type Item l | fromList :: [Item l] -> l | | In the following I give useful instances of the IsList class. | | instance IsList [a] where | type Item [a] = a | fromList = id | | instance (Ord a) => IsList (Set a) where | type Item (Set a) = a | fromList = Set.fromList | | instance (Ord k) => IsList (Map k v) where | type Item (Map k v) = (k,v) | fromList = Map.fromList | | instance IsList (IntMap v) where | type Item (IntMap v) = (Int,v) | fromList = IntMap.fromList | | instance IsList Text where | type Item Text = Char | fromList = Text.pack | | As you can see the extension would allow list literals to be used for sets, maps and | integer maps. In addition the suggested OverloadedLists extension would subsume | OverloadedStrings extension (see the instance for Text, for example). Having said | that, for now, I am not suggesting to remove the OverloadedStrings extension as it | appears to be widely used. | | This extension could also be used for giving data-parallel array literals instead of | the special syntax used currently. | | Unless there is a vocal opposition to the aforementioned two proposals, I would like | to implement them in GHC. Both changes appear to be straightforward to implement. | | Thanks in advance for your feedback. | | Cheers, George | | [1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

George Giorgidze wrote:
My second proposal is to introduce the OverloadedLists extension that overloads list literals...
I am opposed to this proposal as stated. But I think that with a modification, it can not only be improved, but also solve the problems with the current OverloadedStrings extension. OverloadedStrings - and George's unmodified proposal - change compile time errors into run time errors. Literals with hard-to-find problems are accepted by the compiler and become _|_ at run time. An example of the problem: the xml-types package has an IsString instance for Name. The fromString method parses XML namespaces from XML names and calls error if the parse fails. Without the extension, one would specify the parts using constructors; that is wordy and awkward but checked at compile time. A quasi-quoter could be defined, but that syntax would still be far less convenient in practice than string literals. I agree that we need a way of allowing literals to have some flexibility in their types. But there should be a way for overloading to work at compile time, i.e. more like a quasi-quoter, when needed. Of course, "quasi-quoter" overloading can also just create an expression that applies a coercion function at run time. So in that sense, "quasi-quoter" overloading is more general than ad-hoc-polymorphism overloading. In all of George's examples fromList happens to be total, so there isn't an issue having it happen at run time. But if we make this generally available, you can be certain that it will cause problems later on. Just as with IsString, people will not be able to resist the nice syntax, and they will define fromList implementations that are partial. Here is a tentative modification of George's proposal: class IsList l where type Item l fromList :: [Item l] -> l listExpQ :: [ExpQ] -> ExpQ -- Minimal complete definition: fromList listExpQ = appE (varE (mkName "fromList")) . listE If the type of a list literal determines a specific instance of IsList at compile time, use the listExpQ from that instance to interpret the list literal. Otherwise, use the default listExpQ, which is just George's original proposal. An alternative would be to put listExpQ in a separate type class with an IsList constraint. IsString can similarly be extended in a backward compatible way to allow syntax checking at compile time. Here the type could be stringExpQ :: String -> ExpQ Numeric literals with Num and Integral can also be extended, though I think the problem is less common for those. Thanks, Yitz

On Tue, Oct 4, 2011 at 3:25 PM, Yitzchak Gale
George Giorgidze wrote:
My second proposal is to introduce the OverloadedLists extension that overloads list literals...
I am opposed to this proposal as stated.
But I think that with a modification, it can not only be improved, but also solve the problems with the current OverloadedStrings extension.
OverloadedStrings - and George's unmodified proposal - change compile time errors into run time errors. Literals with hard-to-find problems are accepted by the compiler and become _|_ at run time.
An example of the problem: the xml-types package has an IsString instance for Name. The fromString method parses XML namespaces from XML names and calls error if the parse fails. Without the extension, one would specify the parts using constructors; that is wordy and awkward but checked at compile time. A quasi-quoter could be defined, but that syntax would still be far less convenient in practice than string literals.
I agree that we need a way of allowing literals to have some flexibility in their types. But there should be a way for overloading to work at compile time, i.e. more like a quasi-quoter, when needed.
Of course, "quasi-quoter" overloading can also just create an expression that applies a coercion function at run time. So in that sense, "quasi-quoter" overloading is more general than ad-hoc-polymorphism overloading.
In all of George's examples fromList happens to be total, so there isn't an issue having it happen at run time. But if we make this generally available, you can be certain that it will cause problems later on. Just as with IsString, people will not be able to resist the nice syntax, and they will define fromList implementations that are partial.
Here is a tentative modification of George's proposal:
class IsList l where type Item l fromList :: [Item l] -> l listExpQ :: [ExpQ] -> ExpQ
-- Minimal complete definition: fromList listExpQ = appE (varE (mkName "fromList")) . listE
listExpQ doesn't actually use the class's type variable here. You'd have to add a dummy parameter ('l' or preferably 'Proxy l'). That said, this seems like what the Lift class[1] was made for. Maybe: class Lift l => IsList l where fromList :: [Item l] -> l and then have GHC apply the function at compile time, during the Template Haskell phase, and then lift and splice the result. That would resolve both your complaint about partial instances (an exception at compile time is a compile error) and Roman's about performance (if it results in a performance hit with some data structures, it'll only be at compile time). I don't know if it would work out mechanically (i.e. whether GHC's internals allow this kind of thing). In the spirit of "don't let the perfect be the enemy of the good" though, I'm solidly in favor of the original proposal as it is. My only quibble is whether it might not be better called FromList (or FromListLiteral or ...), given that a Map Is not really a List. Since IsString is named the same way, the question is whether consistency or accuracy is more important. [1] http://hackage.haskell.org/packages/archive/template-haskell/2.4.0.0/doc/htm...
If the type of a list literal determines a specific instance of IsList at compile time, use the listExpQ from that instance to interpret the list literal. Otherwise, use the default listExpQ, which is just George's original proposal.
An alternative would be to put listExpQ in a separate type class with an IsList constraint.
IsString can similarly be extended in a backward compatible way to allow syntax checking at compile time. Here the type could be stringExpQ :: String -> ExpQ
Numeric literals with Num and Integral can also be extended, though I think the problem is less common for those.
Thanks, Yitz
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Work is punishment for failing to procrastinate effectively.

2011/10/4 Gábor Lehel
On Tue, Oct 4, 2011 at 3:25 PM, Yitzchak Gale
wrote: George Giorgidze wrote:
My second proposal is to introduce the OverloadedLists extension that overloads list literals...
I am opposed to this proposal as stated.
But I think that with a modification, it can not only be improved, but also solve the problems with the current OverloadedStrings extension.
OverloadedStrings - and George's unmodified proposal - change compile time errors into run time errors. Literals with hard-to-find problems are accepted by the compiler and become _|_ at run time.
An example of the problem: the xml-types package has an IsString instance for Name. The fromString method parses XML namespaces from XML names and calls error if the parse fails. Without the extension, one would specify the parts using constructors; that is wordy and awkward but checked at compile time. A quasi-quoter could be defined, but that syntax would still be far less convenient in practice than string literals.
I agree that we need a way of allowing literals to have some flexibility in their types. But there should be a way for overloading to work at compile time, i.e. more like a quasi-quoter, when needed.
Of course, "quasi-quoter" overloading can also just create an expression that applies a coercion function at run time. So in that sense, "quasi-quoter" overloading is more general than ad-hoc-polymorphism overloading.
In all of George's examples fromList happens to be total, so there isn't an issue having it happen at run time. But if we make this generally available, you can be certain that it will cause problems later on. Just as with IsString, people will not be able to resist the nice syntax, and they will define fromList implementations that are partial.
Here is a tentative modification of George's proposal:
class IsList l where type Item l fromList :: [Item l] -> l listExpQ :: [ExpQ] -> ExpQ
-- Minimal complete definition: fromList listExpQ = appE (varE (mkName "fromList")) . listE
listExpQ doesn't actually use the class's type variable here. You'd have to add a dummy parameter ('l' or preferably 'Proxy l').
That said, this seems like what the Lift class[1] was made for. Maybe:
class Lift l => IsList l where fromList :: [Item l] -> l
and then have GHC apply the function at compile time, during the Template Haskell phase, and then lift and splice the result. That would resolve both your complaint about partial instances (an exception at compile time is a compile error) and Roman's about performance (if it results in a performance hit with some data structures, it'll only be at compile time). I don't know if it would work out mechanically (i.e. whether GHC's internals allow this kind of thing).
In the spirit of "don't let the perfect be the enemy of the good" though, I'm solidly in favor of the original proposal as it is. My only quibble is whether it might not be better called FromList (or FromListLiteral or ...), given that a Map Is not really a List. Since IsString is named the same way, the question is whether consistency or accuracy is more important.
(Of course I mean that if we can get something better, great, but the original proposal is a lot better than nothing - not that I would actually prefer the original to something better than it.)
[1] http://hackage.haskell.org/packages/archive/template-haskell/2.4.0.0/doc/htm...
If the type of a list literal determines a specific instance of IsList at compile time, use the listExpQ from that instance to interpret the list literal. Otherwise, use the default listExpQ, which is just George's original proposal.
An alternative would be to put listExpQ in a separate type class with an IsList constraint.
IsString can similarly be extended in a backward compatible way to allow syntax checking at compile time. Here the type could be stringExpQ :: String -> ExpQ
Numeric literals with Num and Integral can also be extended, though I think the problem is less common for those.
Thanks, Yitz
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Work is punishment for failing to procrastinate effectively.
-- Work is punishment for failing to procrastinate effectively.

| In the spirit of "don't let the perfect be the enemy of the good" | though, I'm solidly in favor of the original proposal as it is. This is my thought too. George is proposing to extend Haskell's existing mechanism for numeric literals (namely, replace 4 by (fromInteger (4::Integer))), so that it works for lists, just as Lennart did for Strings. One could do more, as Yitz has suggested, but that would be an altogether bigger deal, involving Template Haskell and quite a bit of new design; and if done should apply uniformly to numeric and string literals too. So personally I favour George's general approach as a first step. But here is one thought. In the spirit of monad comprehensions, should we not treat [a,b,c] as short for return a `mappend` return b `mappend` return c so that [a,b,c] syntax is, like [ e | x <- xs ] syntax, just short for monadic goop. Then we would not need a new class at all, which would be nice. That isn't quite what Roman was suggesting (he wanted to supply the 'cons' and 'nil') but it's closer, less "head-biased", and it seems to fit the spirit of monad comprehensions. I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals. Simon

Simon Peyton-Jones wrote:
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
What data structures other than lists do we want to construct using list literals? I'm not really sure what the use cases are. Roman

On Wed, Oct 5, 2011 at 8:23 AM, Roman Leshchinskiy
Simon Peyton-Jones wrote:
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
What data structures other than lists do we want to construct using list literals? I'm not really sure what the use cases are.
Maps and Sets are nice, since we don't have syntax sugar for them. -- Felipe.

Roman Leshchinskiy:
Simon Peyton-Jones wrote:
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
What data structures other than lists do we want to construct using list literals? I'm not really sure what the use cases are.
Parallel arrays! (I want to get rid of our custom syntax.) Manuel

For instance, at your day job, the Array type.
On Wed, Oct 5, 2011 at 12:23 PM, Roman Leshchinskiy
Simon Peyton-Jones wrote:
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
What data structures other than lists do we want to construct using list literals? I'm not really sure what the use cases are.
Roman
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

2011/10/5 Simon Peyton-Jones
| In the spirit of "don't let the perfect be the enemy of the good" | though, I'm solidly in favor of the original proposal as it is.
This is my thought too. George is proposing to extend Haskell's existing mechanism for numeric literals (namely, replace 4 by (fromInteger (4::Integer))), so that it works for lists, just as Lennart did for Strings. One could do more, as Yitz has suggested, but that would be an altogether bigger deal, involving Template Haskell and quite a bit of new design; and if done should apply uniformly to numeric and string literals too.
So personally I favour George's general approach as a first step. But here is one thought. In the spirit of monad comprehensions, should we not treat [a,b,c] as short for return a `mappend` return b `mappend` return c so that [a,b,c] syntax is, like [ e | x <- xs ] syntax, just short for monadic goop. Then we would not need a new class at all, which would be nice.
I prefer the flexibility of George's proposal. Of the examples from his email, the only one this design works for is [a].
That isn't quite what Roman was suggesting (he wanted to supply the 'cons' and 'nil') but it's closer, less "head-biased", and it seems to fit the spirit of monad comprehensions.
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
Simon
-- Work is punishment for failing to procrastinate effectively.

Hi all, Simon PJ wrote:
should we not treat [a,b,c] as short for return a `mappend` return b `mappend` return c
[...]
I'm not sure if this plan would support [("fred",45), ("bill",22)] :: Map String Int. Probably not. Maybe that's a shortcoming... but such Maps are a rather surprising use of list literals.
Maybe. But not more surprising than how, say, numeric literals are used in many EDSLs. I also like George's proposal. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

2011/10/5 Simon Peyton-Jones
| In the spirit of "don't let the perfect be the enemy of the good" | though, I'm solidly in favor of the original proposal as it is.
This is my thought too. George is proposing to extend Haskell's existing mechanism for numeric literals (namely, replace 4 by (fromInteger (4::Integer))), so that it works for lists, just as Lennart did for Strings. One could do more, as Yitz has suggested, but that would be an altogether bigger deal, involving Template Haskell and quite a bit of new design; and if done should apply uniformly to numeric and string literals too.
So personally I favour George's general approach as a first step. But here is one thought. In the spirit of monad comprehensions, should we not treat [a,b,c] as short for return a `mappend` return b `mappend` return c so that [a,b,c] syntax is, like [ e | x <- xs ] syntax, just short for monadic goop. Then we would not need a new class at all, which would be nice.
No, you should not. Most of the types of interest (Sets, Maps, arrays) are not monads. Conflating list comprehensions with monads is a huge mistake, and this would repeat it. -Jan

George Giorgidze wrote:
This extension could also be used for giving data-parallel array literals instead of the special syntax used currently.
Unfortunately, it couldn't. DPH array literals don't (and can't really) go through lists. In general, if we are going to overload list literals then forcing the desugaring to always go through lists seems wrong to me. There are plenty of data structures where that might result in a significant performance hit. Roman

Roman Leshchinskiy wrote:
In general, if we are going to overload list literals then forcing the desugaring to always go through lists seems wrong to me. There are plenty of data structures where that might result in a significant performance hit.
These are literals. So the lists will almost always be quite short, and they will be evaluated only once. So I don't think there will be that much of a performance hit normally. That said, my extension that allows them to be desugared at compile time would solve that issue if it arises. Regards, Yitz

Yitzchak Gale wrote:
Roman Leshchinskiy wrote:
In general, if we are going to overload list literals then forcing the desugaring to always go through lists seems wrong to me. There are plenty of data structures where that might result in a significant performance hit.
These are literals. So the lists will almost always be quite short, and they will be evaluated only once. So I don't think there will be that much of a performance hit normally.
Calling them literals is misleading, IMO. They won't necessarily be only evaluated once: f x = [x] In DPH, it wasn't uncommon for certain benchmarks to spend 90% of the time constructing arrays from [:x,y,z:] terms until we made a significant effort to ensure that this doesn't happen. This is the only real data point related to this that I have but it does indicate that making the desugaring efficient is quite important.
That said, my extension that allows them to be desugared at compile time would solve that issue if it arises.
Personally, I don't like having desugaring depend on TH at all. I'm not sure think there is a real need for it. This would, IMO, already be better than fromList wrt efficiency: class Cons a where type Elem a empty :: a cons :: Elem a -> a -> a Roman

Just anecdotally I remember we had this problem with Accelerate.
Back when we were using it last Spring for some reason we were forced by the
API to at least nominally go through lists on our way to the GPU -- which we
sorely hoped were deforested! At times (and somewhat unpredictably), we'd
be faced enormous execution times and memory footprints as the runtime tried
to create gigantic lists for feeding to Accelerate.
Other than that -- I like having a nice literal syntax for other types. But
I'm not sure that I construct literals for Sets and IntMaps often enough to
profit much...
-Ryan
On Tue, Oct 4, 2011 at 9:38 AM, Roman Leshchinskiy
George Giorgidze wrote:
This extension could also be used for giving data-parallel array literals instead of the special syntax used currently.
Unfortunately, it couldn't. DPH array literals don't (and can't really) go through lists.
In general, if we are going to overload list literals then forcing the desugaring to always go through lists seems wrong to me. There are plenty of data structures where that might result in a significant performance hit.
Roman
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Fri, Sep 30, 2011 at 7:28 PM, George Giorgidze
GHC Users,
I would like to make to the following two proposals: * Eliminate the default grouping close from SQL-like comprehensions * Introduce a GHC extension for list literal overloading
OK, let me start with the first proposal.
Currently, the SQL-like comprehension notation (both in its list comprehension and monad comprehension variants) features the following five clauses:
then f then f by e then group by e then group using f then group by e using f
The first two clauses are used for specifying transformations of type [a] -> [a] (or Monad m => m a-> m a for monad comprehensions). The following three clauses are used for specifying transformations of type [a] -> [[a]] (or Monad m, Functor f => m a -> m (f a) for monad comprehensions). See [1] for further details.
Note that the third clause does not mention which function is used for grouping. In this case GHC.Exts.groupWith function is used as a default for list comprehensions and the mgroupWith function from the MonadGroup class is used as a default for monad comprehensions.
I would like to suggest to remove the third clause for the following reasons: * Currently the syntax is asymmetrical. Note that there is the default case for the 'then group' clause and not for the 'then' clause. * In the current notation it is not clear which grouping function is used in the default case * For many monads including lists it is not clear which function should be selected as a default (e.g., the groupWith function also does sorting and it is not clear to me why this should be the default) * Gets rid of the MonadGroup class. Currently the sole purpose of this class is to introduce a default grouping function for monad comprehensions. * Explicit mention of the grouping function would make monad/list comprehensions much easier to read by making it immediately apparent which function is used for grouping.
My second proposal is to introduce the OverloadedLists extension that overloads list literals. See Section 5.2 in [1] for details.
Basically the idea is to treat list literals like:
[1,2,3]
as
fromList [1,2,3]
where
class IsList l where type Item l fromList :: [Item l] -> l
In the following I give useful instances of the IsList class.
instance IsList [a] where type Item [a] = a fromList = id
instance (Ord a) => IsList (Set a) where type Item (Set a) = a fromList = Set.fromList
instance (Ord k) => IsList (Map k v) where type Item (Map k v) = (k,v) fromList = Map.fromList
instance IsList (IntMap v) where type Item (IntMap v) = (Int,v) fromList = IntMap.fromList
instance IsList Text where type Item Text = Char fromList = Text.pack
...one more thought: would this work together with instances of Enum? Could you write: letters :: Text letters = ['a'..'z']
As you can see the extension would allow list literals to be used for sets, maps and integer maps. In addition the suggested OverloadedLists extension would subsume OverloadedStrings extension (see the instance for Text, for example). Having said that, for now, I am not suggesting to remove the OverloadedStrings extension as it appears to be widely used.
This extension could also be used for giving data-parallel array literals instead of the special syntax used currently.
Unless there is a vocal opposition to the aforementioned two proposals, I would like to implement them in GHC. Both changes appear to be straightforward to implement.
Thanks in advance for your feedback.
Cheers, George
[1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Work is punishment for failing to procrastinate effectively.

Am Freitag, den 30.09.2011, 19:28 +0200 schrieb George Giorgidze:
Basically the idea is to treat list literals like:
[1,2,3]
as
fromList [1,2,3]
where
class IsList l where type Item l fromList :: [Item l] -> l
Could we *please* not have classes whose names start with “Is”? We don’t have classes IsNum, IsEq, or IsOrd, so why should we have IsList and IsString? I know that the identifier String is already taken, but please don’t tie an identifier like IsString or IsList to a language feature, so that it’ll be difficult to change it later. Let’s search for a better solution.
In the following I give useful instances of the IsList class.
[…]
instance (Ord a) => IsList (Set a) where type Item (Set a) = a fromList = Set.fromList
As a set is definitely not a list, the class should better be named differently anyway, shouldn’t it? Don’t know if these issues have already been pointed out, since I didn’t read through the complete thread. Sorry, if they have already. Best wishes, Wolfgang
participants (12)
-
Felipe Almeida Lessa
-
George Giorgidze
-
Gábor Lehel
-
Henrik Nilsson
-
Jan-Willem Maessen
-
Lennart Augustsson
-
Manuel M T Chakravarty
-
Roman Leshchinskiy
-
Ryan Newton
-
Simon Peyton-Jones
-
Wolfgang Jeltsch
-
Yitzchak Gale