group keyword with TransformListComp

Don Stewart dons at galois.com
Sun Jun 21 15:34:45 EDT 2009


Don't use TransformListComp ??

-- Don

ndmitchell:
> 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
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list