implicit params in instance contexts

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]

| 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 don't I changed this intentionally, but the type system has been refactored so massively over the years (it's way better than before!) that it's entirely possible it happened as an unintentional consequence. There is actually a good reason. For a function f :: (?x::Int) => blah it's clear where 'f' occurs, and hence which ?x you get: g y = let ?x=4 in ....(let ?x=5 in ...f...) ...f... The first call to 'f' sees ?x=5, and the second sees ?x=4. IP bindings are like local instance declarations. But suppose we had class D a where { op :: a -> a } instance (?x::Int) => D Int where ... g y = let ?x=4 in ....(let ?x=5 in ...op (y::Int)...) ...... The call to op gives rise to a constraint (D Int). Where does that constraint get solved? Right at the call to 'op'? Then it'll see ?x=5? or further out? then it'll see ?x=4. Or at top level? Then it won't see a binding for ?x at all. This is bad. Currently the site at which instance declarations are used isn't important, but now it would become important, and the semantics of the program would depend on it. I think I should disable it again! Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Ganesh Sittampalam | Sent: 16 July 2013 07:21 | To: glasgow-haskell-users@haskell.org | Subject: implicit params in instance contexts | | 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.html#idp49069584) | 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] | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Mon, Jul 15, 2013 at 11:21 PM, Ganesh Sittampalam
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.
There was a post about this previously: http://joyoftypes.blogspot.com/2013/01/using-compiler-bugs-for-fun-and-profi... And a GHC ticket: http://ghc.haskell.org/trac/ghc/ticket/7624 See also the discussion at http://www.reddit.com/r/haskell/comments/178w9u/using_compiler_bugs_for_fun_... Shachaf

GHC ticket:
http://ghc.haskell.org/trac/ghc/ticket/7624
2013/7/16 Ganesh Sittampalam
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]
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (4)
-
Ganesh Sittampalam
-
Krzysztof Gogolewski
-
Shachaf Ben-Kiki
-
Simon Peyton-Jones