Two Proposals
George Giorgidze
giorgidze at gmail.com
Tue Oct 11 00:21:50 CEST 2011
A quick thought that came to me after hoogling [a] -> [[a]].
The first four functions in the search result are named after what they return (noun in plural) rather than what they do (verb). I am talking about inits, permutations, subsequence and tails.
So I thought the following syntax might work as well if (as it is already common) grouping functions are named after what they return.
then f
then f by e
then group f
then group f by e
For example the following code fragments read well:
then group inits
then group permutations
then group subsequences
then group tails
Here we use the special identifier group as a verb.
I have not told you about the fifth result of the hoogling, the groupWith function. The following really looks ugly:
then group groupWith by e
But following the aforementioned naming convention the groupWith function could as well be named as equals. Now this reads well:
then group equals by e
Cheers, George
On 2011-Oct-5, at 09:14 , Simon Peyton-Jones wrote:
> [adding ghc-users]
>
> It's not easy, Phil. Do you have any ideas?
>
> For the 'then' case the name of the function serves as the verb. One might say
>
> then take 4
> or
> then takeWhile by salary > 40
>
> For grouping one might like to say the same thing, such as
> then groupBy by salary
> but the typing rule is quite different, so we really need a different keyword. We chose the compound keyword "then group" to avoid needing a whole new keyword ("group" is treated specially only in tthis context). So you write
> then group by salary using groupBy
>
> Using this order of the pieces for the sorting case is harder. What would one say? "then process"? Like this?
> then process by salary > 40 using takeWhile
> Not very nice.
>
> One could use a new keyword for grouping "theng" say, thus:
> theng groupBy by salary
> But that is hardly beautiful either.
>
> So the current story is not great, but it's the best I could think of. Improvements welcome.
>
> Simon
>
> | -----Original Message-----
> | From: Philip Wadler [mailto:wadler at inf.ed.ac.uk]
> | Sent: 04 October 2011 18:15
> | To: Simon Peyton-Jones; George Giorgidze
> | Subject: Re: FW: Two Proposals
> |
> | George,
> |
> | Nice proposal. I like the idea of symmetry, but don't at all like the
> | idea that f comes before e for 'then' but f comes after e for 'then
> | group'. Can you rethink it and come up with something even more
> | symmetric?
> |
> | Yours, -- P
> |
> |
> | On Tue, Oct 4, 2011 at 9:23 AM, Simon Peyton-Jones
> | <simonpj at microsoft.com> wrote:
> | > FYI
> | >
> | > -----Original Message-----
> | > From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
> | users-bounces at haskell.org] On Behalf Of George Giorgidze
> | > Sent: 30 September 2011 18:28
> | > To: glasgow-haskell-users at 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 at haskell.org
> | > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> | >
> | >
> | >
> |
> |
> |
> | --
> | .\ Philip Wadler, Professor of Theoretical Computer Science
> | ./\ School of Informatics, University of Edinburgh
> | / \ http://homepages.inf.ed.ac.uk/wadler/
> |
> | The University of Edinburgh is a charitable body, registered in
> | Scotland, with registration number SC005336.
> |
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20111011/2ec740cb/attachment-0001.htm>
More information about the Glasgow-haskell-users
mailing list