[Haskell-cafe] Noticed this change about infix decls in GHC 7.4.2

Christopher Done chrisdone at googlemail.com
Sun Jun 17 20:53:47 CEST 2012


So I have some module, in a work project that I'm portnig from GHC
6.12.3 to GHC 7.4.2,

module Data.Monoid.Operator where

import Data.Monoid

(++) :: Monoid a => a -> a -> a
(++) = mappend
infixr 5 ++

This compiles happily on GHC 6.12.3, but on 7.4.2 says:

src/Data/Monoid/Operator.hs:9:10:
    Ambiguous occurrence `++'
    It could refer to either `Data.Monoid.Operator.++',
                             defined at src/Data/Monoid/Operator.hs:8:1
                          or `Prelude.++',
                             imported from `Prelude' at
src/Data/Monoid/Operator.hs:3:8-27
                             (and originally defined in `GHC.Base')

It seems that it used to assign higher priority to the declared thing
in the current module over the imported one. Is this intentional? I'd
suspect not, given that if I comment the binding out:

-- (++) :: Monoid a => a -> a -> a
-- (++) = mappend

I get:

src/Data/Monoid/Operator.hs:9:10:
    The fixity signature for `++' lacks an accompanying binding
      (The fixity signature must be given where `++' is declared)

Which seems to contradict the previous error message.

Bug?

Ciao!

P.S. Yes, I know I can fix this by not importing Prelude.
P.P.S Yes, I know there's a <> or <+> defined now, but I prefer (++), thanks.



More information about the Haskell-Cafe mailing list