 
            On Feb 7, 2008 9:01 PM, Dan Weston 
This may be a GHC bug, but even though in the module Data.TypeLevel.Num.Reps has the header
{-# LANGUAGE EmptyDataDecls, TypeOperators #-}
I still get an error with both ghc and ghci version 6.8.2 unless I throw in the -XTypeOperators flag.
If you are using type operators in a module you have to supply the flag, independently of what flags are supplied in other modules. The same applies for other extensions which modify the _syntax_ of the language (e.g. Template Haskell etc ...) So, it's not a bug. As a side note, even if the TypeOperators flag is supplied GHC 6.8.2 fires an error with the following declaration: instance (Compare x y CEQ) => x :==: y -- GHC fires a "Malformed instance header" error whereas using an equivalent prefix definition works just fine instance (Compare x y CEQ) => (:==:) x y