
Hi, It seems that from GHC 7.4, the prohibition on implicit parameter constraints in instance declarations has been relaxed. The program below gives the error "Illegal constraint ?fooRev::Bool" in GHC 7.2.1 but loads fine in GHC 7.4.2 and GHC 7.6.2. I can't spot anything about this in the release notes, and the documentation (http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/other-type-extensions...) still says "You can't have an implicit parameter in the context of a class or instance declaration." So I wonder if this happened by accident, perhaps as part of the ConstraintKinds work or similar? I've wanted this feature a few times so if it's going to stay I might start using it. However it is a bit dangerous, so if it was added by accident it might warrant some discussion before deciding to keep it. For example as the value "set2" below shows, it can be used to violate datatype invariants. Cheers, Ganesh {-# LANGUAGE ImplicitParams #-} module Ord where import Data.Set ( Set ) import qualified Data.Set as Set newtype Foo = Foo Int deriving (Eq, Show) instance (?fooRev :: Bool) => Ord Foo where Foo a `compare` Foo b = if ?fooRev then b `compare` a else a `compare` b set1 = let ?fooRev = False in Set.fromList [Foo 1, Foo 3] set2 = let ?fooRev = True in Set.insert (Foo 2) set1 -- Ord> set2 -- fromList [Foo 2,Foo 1,Foo 3]