[GHC] #13267: Constraint synonym instances

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Something funny happens when you try to declare an instance of a constraint synonym: {{{ {-# LANGUAGE ConstraintKinds #-} module F where type ShowF a = Show (a -> Bool) instance ShowF Int where show _ = "Fun" }}} I get: {{{ F.hs:8:5: error: ‘show’ is not a (visible) method of class ‘ShowF’ | 8 | show _ = "Fun" | ^^^^ }}} OK, but it gets weirder. Look at: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances #-} module F where type ShowF a = (Show (a -> Bool)) instance ShowF Int where }}} This is accepted (with a complaint that `show` is not implemented.) It gets even more awful: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} module F where type ShowF a = (Show Bool, Show Int) instance ShowF Int where }}} This is awful: GHC treats `Show Bool` and `Show Int` as if they were constraints, and then emits the following DFun: {{{ df9d1b4635f2a752f29ff327ab66d1cb $f(%,%)ShowShow :: (Show Bool, Show Int) DFunId {- Strictness: m, Inline: CONLIKE, Unfolding: DFun: @ a @ b. @ (Show Bool) @ (Show Int) $fShowBool $fShowInt -} }}} I don't even know what this is supposed to mean. OK, so what should we do? I think there are a few possibilities: 1. Completely outlaw instance declarations on constraint synonyms. 2. Allow instance declarations on constraint synonyms, but only if after desugaring the synonym, you end up with a single class head. I would find this useful in a few cases, for example, if you are writing `instance MonadSample (Impl t) MyMonad`, if you had `type MonadSample2 t a = MonadSample (Impl t) a` you might prefer writing `instance MonadSample t MyMonad` instead 3. Figure out what instance declarations with multiple class heads, and proceed accordingly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -73,2 +73,2 @@ - 3. Figure out what instance declarations with multiple class heads, and - proceed accordingly. + 3. Figure out what to do with instance declarations with multiple class + heads, and proceed accordingly. New description: Something funny happens when you try to declare an instance of a constraint synonym: {{{ {-# LANGUAGE ConstraintKinds #-} module F where type ShowF a = Show (a -> Bool) instance ShowF Int where show _ = "Fun" }}} I get: {{{ F.hs:8:5: error: ‘show’ is not a (visible) method of class ‘ShowF’ | 8 | show _ = "Fun" | ^^^^ }}} OK, but it gets weirder. Look at: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances #-} module F where type ShowF a = (Show (a -> Bool)) instance ShowF Int where }}} This is accepted (with a complaint that `show` is not implemented.) It gets even more awful: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} module F where type ShowF a = (Show Bool, Show Int) instance ShowF Int where }}} This is awful: GHC treats `Show Bool` and `Show Int` as if they were constraints, and then emits the following DFun: {{{ df9d1b4635f2a752f29ff327ab66d1cb $f(%,%)ShowShow :: (Show Bool, Show Int) DFunId {- Strictness: m, Inline: CONLIKE, Unfolding: DFun: @ a @ b. @ (Show Bool) @ (Show Int) $fShowBool $fShowInt -} }}} I don't even know what this is supposed to mean. OK, so what should we do? I think there are a few possibilities: 1. Completely outlaw instance declarations on constraint synonyms. 2. Allow instance declarations on constraint synonyms, but only if after desugaring the synonym, you end up with a single class head. I would find this useful in a few cases, for example, if you are writing `instance MonadSample (Impl t) MyMonad`, if you had `type MonadSample2 t a = MonadSample (Impl t) a` you might prefer writing `instance MonadSample t MyMonad` instead 3. Figure out what to do with instance declarations with multiple class heads, and proceed accordingly. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -70,1 +70,1 @@ - MonadSample (Impl t) a` you might prefer writing `instance MonadSample t + MonadSample (Impl t) a` you might prefer writing `instance MonadSample2 t New description: Something funny happens when you try to declare an instance of a constraint synonym: {{{ {-# LANGUAGE ConstraintKinds #-} module F where type ShowF a = Show (a -> Bool) instance ShowF Int where show _ = "Fun" }}} I get: {{{ F.hs:8:5: error: ‘show’ is not a (visible) method of class ‘ShowF’ | 8 | show _ = "Fun" | ^^^^ }}} OK, but it gets weirder. Look at: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances #-} module F where type ShowF a = (Show (a -> Bool)) instance ShowF Int where }}} This is accepted (with a complaint that `show` is not implemented.) It gets even more awful: {{{ {-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} module F where type ShowF a = (Show Bool, Show Int) instance ShowF Int where }}} This is awful: GHC treats `Show Bool` and `Show Int` as if they were constraints, and then emits the following DFun: {{{ df9d1b4635f2a752f29ff327ab66d1cb $f(%,%)ShowShow :: (Show Bool, Show Int) DFunId {- Strictness: m, Inline: CONLIKE, Unfolding: DFun: @ a @ b. @ (Show Bool) @ (Show Int) $fShowBool $fShowInt -} }}} I don't even know what this is supposed to mean. OK, so what should we do? I think there are a few possibilities: 1. Completely outlaw instance declarations on constraint synonyms. 2. Allow instance declarations on constraint synonyms, but only if after desugaring the synonym, you end up with a single class head. I would find this useful in a few cases, for example, if you are writing `instance MonadSample (Impl t) MyMonad`, if you had `type MonadSample2 t a = MonadSample (Impl t) a` you might prefer writing `instance MonadSample2 t MyMonad` instead 3. Figure out what to do with instance declarations with multiple class heads, and proceed accordingly. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): This is a duplicate of some other ticket. As I recall, the problem here is that the renamer wants to resolve the name `show` to a method of a particular class, at a point before we can normalize the type `ShowF`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Let's just do (1) for now. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => polykinds/T13267 * status: new => closed * resolution: => fixed Comment: Not perfect, but enough! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC accepts | Test Case:
invalid program | polykinds/T13267
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => merge * milestone: => 8.2.1 Comment: It would be nice to merge 740ecda32116abe84b6d7d4786b3e2ad9c8ba2a4 into 8.2, which notes this change in the release notes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged to `ghc-8.2` as 3ab6684bdf4abf700cc9b43aaa3d42c38c8ae291. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): I'd like to just note that https://github.com/niteria/dual- tree/blob/master/test/Test.hs now fails to build with: {{{ test/Test.hs:55:19: error: • Illegal instance for a type synonym A class instance must be for a class • In the stand-alone deriving instance for ‘Typeable1 Sum’ | 55 | deriving instance Typeable1 X.Sum | ^^^^^^^^^^^^^^^ test/Test.hs:56:19: error: • Illegal instance for a type synonym A class instance must be for a class • In the stand-alone deriving instance for ‘Typeable1 Product’ | 56 | deriving instance Typeable1 X.Product | ^^^^^^^^^^^^^^^^^^^ }}} I will attach a smaller example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * Attachment "A.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Certainly, since `Typeable1` is a constraint synonym for `Typeable` (since the 7.8 release, where `Typeable` became poly-kinded). But `Typeable1`, `Typeable2`, //et al.// have also been deprecated since 7.8 - surely you can just use `Typeable` instead? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): (And perhaps we should consider removing `Typeable1`, `Typeable2`, etc. entirely?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13267#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC