[GHC] #14643: Partial type signatures in spliced TH declarations behave unexpectedly

#14643: Partial type signatures in spliced TH declarations behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Minimal example: {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE TemplateHaskell #-} module Minimal where id [d| f :: (Monad m, _) => [m a] -> m [a] f' :: (Monad m, _) => [m a] -> m [a] f = f' f' [] = return [] f' (x:xx) = f xx |] }}} {{{ [1 of 1] Compiling Minimal ( /Users/pepe/Dropbox/code/debug- hoed/test/minimal.hs, interpreted ) /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f :: (Monad m_a7NN, _) => [m_a7NN a_a7NO] -> m_a7NN [a_a7NO] | 5 | id [d| | ^^^^^^... /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f' :: (Monad m_a7NL, _) => [m_a7NL a_a7NM] -> m_a7NL [a_a7NM] | 5 | id [d| | ^^^^^^... Ok, one module loaded. :browse f :: (Monad m, Monad m) => [m a] -> m [a] f' :: (Monad m, Monad m) => [m a] -> m [a] }}} Notice the duplicate Monad m constraint. Things get even more weird if the type signatures are declared together: {{{#!hs id [d| f, f' :: (Monad m, _) => [m a] -> m [a] f = f' f' [] = return [] f' (x:xx) = f xx |] }}} {{{ [1 of 1] Compiling Minimal ( /Users/pepe/Dropbox/code/debug- hoed/test/minimal.hs, interpreted ) /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f :: (Monad m_a88E, _) => [m_a88E a_a88F] -> m_a88E [a_a88F] | 5 | id [d| | ^^^^^^... /Users/pepe/Dropbox/code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f' :: (Monad m_a88E, _) => [m_a88E a_a88F] -> m_a88E [a_a88F] | 5 | id [d| | ^^^^^^... Ok, one module loaded. :browse f :: (Monad ghc-prim-0.5.1.1:GHC.Types.Any, Monad m) => [ghc-prim-0.5.1.1:GHC.Types.Any ghc-prim-0.5.1.1:GHC.Types.Any] -> ghc-prim-0.5.1.1:GHC.Types.Any [ghc-prim-0.5.1.1:GHC.Types.Any] f' :: (Monad ghc-prim-0.5.1.1:GHC.Types.Any, Monad m) => [m a] -> m [a] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in spliced TH declarations behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): It looks the same under ghc 8.4 alpha: {{{ GHCi, version 8.4.0.20171214: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Minimal ( code/debug-hoed/test/minimal.hs, interpreted ) code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f :: (Monad m_a46U, _) => [m_a46U a_a46V] -> m_a46U [a_a46V] | 5 | id [d| | ^^^^^^... code/debug-hoed/test/minimal.hs:5:1: warning: [-Wpartial-type-signatures] • Found type wildcard ‘_’ standing for ‘()’ • In the type signature: f' :: (Monad m_a46U, _) => [m_a46U a_a46V] -> m_a46U [a_a46V] | 5 | id [d| | ^^^^^^... Ok, one module loaded. *Minimal> :browse f :: (Monad GHC.Types.Any, Monad m) => [GHC.Types.Any GHC.Types.Any] -> GHC.Types.Any [GHC.Types.Any] f' :: (Monad GHC.Types.Any, Monad m) => [m a] -> m [a] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures interact unexpectedly with :browse -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Note that this has nothing to do with Template Haskell. You can also trigger the issue with this (slightly more) minimal file: {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE TemplateHaskell #-} module Bug where f :: (Monad m, _) => [m a] -> m [a] f' :: (Monad m, _) => [m a] -> m [a] f = f' f' [] = return [] f' (x:xx) = f xx g, g' :: (Monad m, _) => [m a] -> m [a] g = g' g' [] = return [] g' (x:xx) = g xx }}} {{{ $ ghci Bug.hs -Wno-partial-type-signatures GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Ok, one module loaded. λ> :browse f :: (Monad m, Monad m) => [m a] -> m [a] f' :: (Monad m, Monad m) => [m a] -> m [a] g :: (Monad GHC.Types.Any, Monad m) => [GHC.Types.Any GHC.Types.Any] -> GHC.Types.Any [GHC.Types.Any] g' :: (Monad GHC.Types.Any, Monad m) => [m a] -> m [a] }}} The same behavior also happens with `:type v` (but not `:type`, since that performs deep instantiation of the types): {{{ λ> :type +v f f :: (Monad m, Monad m) => [m a] -> m [a] λ> :type +v f' f' :: (Monad m, Monad m) => [m a] -> m [a] λ> :type +v g g :: (Monad GHC.Types.Any, Monad m) => [GHC.Types.Any GHC.Types.Any] -> GHC.Types.Any [GHC.Types.Any] λ> :type +v g' g' :: (Monad GHC.Types.Any, Monad m) => [m a] -> m [a] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in class constraints behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mnislaih): Hi Ryan, thanks for the even smaller example! For some reason I didn't think of removing the TH splice. But just to clarify, this issue is not restricted to `:browse`. The resulting type signatures with `Any` in them cannot be instantiated, or at least I haven't figured out how. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in class constraints behave unexpectedly
-------------------------------------+-------------------------------------
Reporter: mnislaih | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14643: Partial type signatures in class constraints behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T14643, T14643a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => partial-sigs/should_compile/T14643, T14643a * status: new => merge Comment: Thanks for the report. It was trickier than I thought, and showed up not one but two separate bugs. We could merge this... it's an outright bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in class constraints behave unexpectedly
-------------------------------------+-------------------------------------
Reporter: mnislaih | Owner: (none)
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case: partial-
| sigs/should_compile/T14643, T14643a
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14643: Partial type signatures in class constraints behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T14643, T14643a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): If you merge, merge both! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in class constraints behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T14643, T14643a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.4.1 Comment: Merged in 3d2664e4d97fde24f4a70d3fd106618d41c55776 and 8553593731872dc9d33edca3afc9088d40fe75ed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14643: Partial type signatures in class constraints behave unexpectedly -------------------------------------+------------------------------------- Reporter: mnislaih | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: | PartialTypeSignatures Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T14643, T14643a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => PartialTypeSignatures -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14643#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC