[GHC] #12220: TypeApplications and DefaultSignatures - problems deducing type variables.

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux DefaultSignatures, | TypeApplications | Architecture: x86_64 | Type of failure: None/Unknown (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following example code throws an error. The example code: {{{#!hs {-#LANGUAGE TypeApplications#-} {-#LANGUAGE MultiParamTypeClasses #-} {-#LANGUAGE AllowAmbiguousTypes #-} {-#LANGUAGE FlexibleInstances #-} {-#LANGUAGE ScopedTypeVariables #-} {-#LANGUAGE DefaultSignatures #-} module Test1 where -- | Type a is only used for -- type application. class ToUse a where toUse :: Int -> Int -- | The type used for -- type application data Default -- | The instance using Default as type application. -- To call use: -- > toUse @Default instance ToUse Default where toUse a = 3*a -- | Typeclass whose methods work -- only with type application. class (ToUse a) => Uses a b where uses :: b -> [b] -- | Default Signature, which generates the problem. -- It is the same as the normal one -- Comment it to 'fix' the bug. default uses :: b -> [b] uses v = [v] -- | Normal instances, nothing special instance Uses Default Int where uses v = take (toUse @Default 3) $ repeat v -- | Another normal one instance Uses Default String where uses v = take (toUse @Default 2) $ repeat v -- | This one works nicely instance (ToUse t, Uses t a, Uses t b) => Uses t (a,b) where uses (vl,vr) = zip ls rs where ls = uses @t vl rs = uses @t vr -- | But this one doesn't. -- Unless you comment the default signature. instance (ToUse t, Uses t a, Uses t b, Uses t c) => Uses t (a,b,c) }}} The error: {{{ • Could not deduce (Uses a0 a) arising from a use of ‘Test1.$dmuses’ from the context: (ToUse t, Uses t a, Uses t b, Uses t c) bound by the instance declaration at Test1.hs:47:10-66 The type variable ‘a0’ is ambiguous Relevant bindings include uses :: (a, b, c) -> [(a, b, c)] (bound at Test1.hs:47:10) • In the expression: Test1.$dmuses In an equation for ‘uses’: uses = Test1.$dmuses In the instance declaration for ‘Uses t (a, b, c)’ }}} Commenting out the default signature fixes the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables.
-------------------------------------+-------------------------------------
Reporter: mkloczko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
| DefaultSignatures, TypeApplications
Operating System: Linux | Architecture: x86_64
| (amd64)
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => generics/T12220 * milestone: => 8.0.2 Comment: Thanks for reporting this. Now fixed. I think that the fix is non-invasive and so could merge to 8.0.2 Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This isn't quite non-invasive, since it's causing some packages to fail to compile on GHC HEAD that were compiling on GHC 8.0.1. See #12466. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Does anyone care if this doesn't make it into 8.0.1? If it goes in, we'll have to fix #12466 too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: 8.0.2 => 8.2.1 Comment: Given that no one feels terribly strongly about this we'll be bumping it off to 8.2.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.0.2 Comment: It ended up being not so bad to merge afterall. Merged to `ghc-8.0` as 54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables. -------------------------------------+------------------------------------- Reporter: mkloczko | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | DefaultSignatures, TypeApplications Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | generics/T12220 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This also introduced another typechecker regression in GHC 8.0.2: #12784. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12220#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12220: TypeApplications and DefaultSignatures - problems deducing type variables.
-------------------------------------+-------------------------------------
Reporter: mkloczko | Owner:
Type: bug | Status: closed
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1
Resolution: fixed | Keywords:
| DefaultSignatures, TypeApplications
Operating System: Linux | Architecture: x86_64
| (amd64)
Type of failure: None/Unknown | Test Case:
| generics/T12220
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC