group keyword with TransformListComp

Max Bolingbroke batterseapower at hotmail.com
Sat Jun 27 06:52:53 EDT 2009


Hi,

I agree this is annoying. It was hard to find syntax which was both
meaningful and currently unused, so we settled on this instead. As
Simon says, suggestions are welcome!

Note that group *should* be parsed as a special id, so you can still
import D.L qualified and then use dot notation to access the function.

Cheers,
Max

2009/6/21 Neil Mitchell <ndmitchell at gmail.com>:
> Hi,
>
> The TransformListComp extension makes group a keyword. Unfortunately
> group is a useful function, and is even in Data.List. Thus,
> Data.List.group and TransformListComp are incompatible. This seems a
> very painful concession to give up a nice function name for a new
> extension. Is this intentional? Here's an example:
>
>> $ cat GroupKeyword.hs
>> {-# LANGUAGE TransformListComp #-}
>> module GroupKeyword where
>>
>> a = map head $ group $ sort [1..100]
>> $ ghci GroupKeyword.hs
>> GHCi, version 6.10.2: http://www.haskell.org/ghc/  :? for help
>> Loading package ghc-prim ... linking ... done.
>> Loading package integer ... linking ... done.
>> Loading package base ... linking ... done.
>> [1 of 1] Compiling GroupKeyword     ( GroupKeyword.hs, interpreted )
>>
>> GroupKeyword.hs:4:15: parse error on input `group'
>> Failed, modules loaded: none.
>> Prelude>
>
> There are some places I'd like to use TransformListComp, but I often
> want to use group in the same module.
>
> Thanks
>
> Neil
>


More information about the Glasgow-haskell-users mailing list