[GHC] #12087: Inconsistency in GADTs?

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: GADTs | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs f :: Ord a => Eq a => a -> Bool f = … }}} this is allowed but not in GADTs {{{#!hs data F a where MkF :: Ord a => Eq a => a -> F a -- <interactive>:48:16: error: -- • Data constructor ‘MkF’ returns type ‘Eq a => a -> F a’ -- instead of an instance of its parent type ‘F a’ -- • In the definition of data constructor ‘MkF’ -- In the data type declaration for ‘F’ }}} not a big deal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid Comment:
f :: Ord a => Eq a => a -> Bool
This is not valid Haskell. See #11540. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) * status: closed => new * resolution: invalid => * related: => #11540 Comment: I disagree that this not "valid" Haskell. It's certainly not //standard// Haskell, but I don't see why it ought to be rejected. Perhaps one day after #11540 is fixed, we'll need some extra language extension enabled to use this feature, but I think GHC is more than capable of handling such a thing. For background context: the structure of GADT type signatures are currently validity checked in a rather simple-minded way in [http://git.haskell.org/ghc.git/blob/86abe0e03f6cc2392758d6b45390177d44896113... gadtDeclDetails]. It splits apart a single `forall` with `splitLHsSigmaTy` and checks if the return type is of the form `T a_1 ... a_n`, where `T` is the GADT tycon. But since there's nested sigma types here, GHC mistakenly believes that the return type is `Eq a => a -> F a`, which is bad news. I think it would be possible to tweak this check to accommodate nested foralls, though. Essentially, I think we'd need to create a version of [http://git.haskell.org/ghc.git/blob/86abe0e03f6cc2392758d6b45390177d44896113... tcSplitNestedSigmaTys] that works over `LHsType` instead of `Type`, and replace the use of `splitLHsSigmaTy` with that in `gadtDeclDetails`. Then we'd typecheck `MkF` as if it had the type `forall a. (Ord a, Eq a) => a -> F a`. This isn't exactly what the user //wrote//, but it's equivalent and serviceable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: (none) => RyanGlScott -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree this is possible in principle but it is fiddly in practice. What about {{{ MkF :: Ord a => a -> Eq a => F a }}} which ought to work too.
This isn't exactly what the user wrote, but it's equivalent and serviceable.
Yes but we'll soon have people asking that `:t MkF` prints out the type they wrote. Nothing deep here I think, but I'm not persuaded that it's a high priority. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:4 simonpj]:
I agree this is possible in principle but it is fiddly in practice. What about {{{ MkF :: Ord a => a -> Eq a => F a }}} which ought to work too.
This isn't exactly what the user wrote, but it's equivalent and serviceable.
Yes but we'll soon have people asking that `:t MkF` prints out the type
Sure, I completely agree. `tcSplitNestedSigmaTys` can handle that case, so `tcSplitNestedLHsSigmaTys` ought to as well. they wrote. We can cross that bridge when we come to it. FWIW, GHC doesn't have a solid track record of preserving nested sigma types for functions either: {{{ λ> let f :: Ord a => Eq a => a -> Bool; f = undefined λ> :type f f :: Ord a => a -> Bool λ> let g :: Ord a => a -> Eq a => a; g = undefined λ> :type g g :: Ord a1 => a2 -> a1 }}} So it (personally) wouldn't bother me to have `:type MkF` print out something slightly different than what I typed. After all, if I'm using nested sigma types in the first place, there's a good chance I know why GHC's displayed type is tweaked (but equivalent). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The underlying issue here -- that the type of GADT constructors is a bit inflexible -- is important in the context of Dependent Haskell. For example, I might want to say {{{#!hs data Foo a where MkFoo :: pi (x :: Type) -> (F x ~ Bool) => Foo x }}} This takes a ''visible'' type `x` and then asserts some constraint on `x`. The constraint must come ''after'' binding `x`, of course! So loosening up these rules will actually increase expressiveness once we have dependent types. Re comment:5, recall that `:type` takes an ''expression'', upon which it performs type inference. Thus it stands to reason that quantifiers, etc., will get shuffled around. This is why `:type +v` got added, so that the type is just reported as is, without any instantiation/regeneralization. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Phab:D3831 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3831 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => new * owner: RyanGlScott => (none) * differential: Phab:D3831 => Comment: Richard and I decided that the approach taken in Phab:D3831 wasn't the best course of action. Although it would allow exotic GADT constructor type signatures like `Ord a => Eq a => a -> F a`, it would come at a steep price: GHC would normalize the type signature to `(Ord a, Eq a) => a -> F a` behind the scenes, so you'd no longer see the type you originally wrote when you queried it with `:type +v`. For this reason, I've decided to try to improve the current error message instead, which doesn't make it very clear what the underlying problem is (nor how to fix it). Patch coming soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Phab:D3851 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3851 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12087: Inconsistency in GADTs?
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: task | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: GADTs
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #11540 | Differential Rev(s): Phab:D3851
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: gadt/T12087 Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Phab:D3851 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => gadt/T12087 * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12087#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC