[GHC] #13249: Default signature check can be quite onerous

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #12918 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The `bytes` library currently doesn't compile with GHC `master` due to the new check of default signatures (7363d5380e600e2ef868a069d5df6857d9e5c17e, #12918). Consider this example, {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DefaultSignatures #-} module Hi where import Control.Monad.Trans.Class class MonadGet m where type Remaining m :: * remaining :: m (Remaining m) default remaining :: (MonadTrans t, MonadGet n, m ~ t n) => m (Remaining (t m)) remaining = lift remaining }}} Patching this up requires a fair amount of hand-holding, {{{#!hs default remaining :: (MonadTrans t, MonadGet n, m ~ t n, Remaining m ~ Remaining n, Monad n) => m (Remaining m) }}} Yuck. I suppose this is just how the world works, but I thought I'd leave this here in case anyone had a clever idea for improvement. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -15,1 +15,1 @@ - (t m)) + (t n)) New description: The `bytes` library currently doesn't compile with GHC `master` due to the new check of default signatures (7363d5380e600e2ef868a069d5df6857d9e5c17e, #12918). Consider this example, {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DefaultSignatures #-} module Hi where import Control.Monad.Trans.Class class MonadGet m where type Remaining m :: * remaining :: m (Remaining m) default remaining :: (MonadTrans t, MonadGet n, m ~ t n) => m (Remaining (t n)) remaining = lift remaining }}} Patching this up requires a fair amount of hand-holding, {{{#!hs default remaining :: (MonadTrans t, MonadGet n, m ~ t n, Remaining m ~ Remaining n, Monad n) => m (Remaining m) }}} Yuck. I suppose this is just how the world works, but I thought I'd leave this here in case anyone had a clever idea for improvement. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well it's true, isn't it? We are simply listing the conditions under which you can use the generic default instance. The more constraints you need, the less generally-applicable it is. In this case you are saying that you can say {{{ instance MonadGet ty where type Remaining ty = blah -- no code for 'remaining' }}} only if: * `ty` is of form `(t n)` * We have `MonadTrans t, MonadGet n, Monad n` * `Remaining (t n)` equals `Remaining n`. Fair enough -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => invalid Comment: Yes, it is true; I was fearing this would pop up in more Hackage packages after running into it very early in my testing. However, so far `bytes` has been the only package where the constraints blew up to this extent. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): What about {{{#!hs default remaining :: (MonadTrans t, Monad m) => t m (Remaining m) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13249: Default signature check can be quite onerous -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12918 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sorry for not noticing this sooner, but I agree with Simon that the situation is not as dire as it seems. It should be noted that the correct default type signature could actually be made a little shorter: {{{#!hs default remaining :: (MonadTrans t, MonadGet n, m ~ t n, Remaining m ~ Remaining n) => m (Remaining m) }}} That is, the `MonadGet n` constraint implies the `Monad n` constraint. I don't think four constraints is a unreasonable amount to ask for, given that we're using the "lift something into a `MonadTrans`" design pattern, which requires repeating the constraints (and associated type families) for the type that is lifted anyway. Also, to answer Iceland_jack's question: no, `t m (Remaining m)` would not be valid, both in the sense that GHC will reject it and in a semantic sense, as you're conflating two different `Monad`s. The first `m` in `t m (Remaining m)` represents the `Monad` you're lifted, while the second `m` is for the type which is a `MonadTrans` (i.e, the thing you're lifting into). Failing to distinguish between these two things has led to all sorts of problems in the past (see #12784), which is one the reasons we introduced this check in the first place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13249#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC