[GHC] #11122: Ambiguous inferred type causes a panic

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: Linux Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program. {{{#!hs {-# LANGUAGE PartialTypeSignatures #-} module Main where import Text.Parsec import Text.Parsec.String parser :: Parser _ parser = read <$> many digit data Wrapper = Wrapper Int wrapperParser = Wrapper <$> parser }}} I am not sure whether it is valid or not, but it breaks the type checker as follows. {{{#!hs Program.hs:9:1: No instance for (Read w_) When checking that ‘parser’ has the specified type parser :: forall w_. Parser w_ Probable cause: the inferred type is ambiguous Program.hs:13:29: Couldn't match type ‘w_’ with ‘Int’ ‘w_’ is untouchable inside the constraints () bound by the inferred type of wrapperParser :: ParsecT String () Data.Functor.Identity.Identity Wrapper at Program.hs:13:1-34ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): No skolem info: w__avnz[sk] }}} Disabling `PartialTypeSignatures` makes no difference. Switching from `parsec-3.1.9` to `megaparsec-4.1.1` and changing `many digit` to `some digitChar` does not have an effect either. Replacing `_` with `Int` seems to be the only obvious way to make the problem disappear. Alas that defeats the point of using partial type signatures or typed holes in the first place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by tuplanolla: Old description:
Consider the following program.
{{{#!hs {-# LANGUAGE PartialTypeSignatures #-}
module Main where
import Text.Parsec import Text.Parsec.String
parser :: Parser _ parser = read <$> many digit
data Wrapper = Wrapper Int
wrapperParser = Wrapper <$> parser }}}
I am not sure whether it is valid or not, but it breaks the type checker as follows.
{{{#!hs Program.hs:9:1: No instance for (Read w_) When checking that ‘parser’ has the specified type parser :: forall w_. Parser w_ Probable cause: the inferred type is ambiguous
Program.hs:13:29: Couldn't match type ‘w_’ with ‘Int’ ‘w_’ is untouchable inside the constraints () bound by the inferred type of wrapperParser :: ParsecT String () Data.Functor.Identity.Identity Wrapper at Program.hs:13:1-34ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): No skolem info: w__avnz[sk] }}}
Disabling `PartialTypeSignatures` makes no difference. Switching from `parsec-3.1.9` to `megaparsec-4.1.1` and changing `many digit` to `some digitChar` does not have an effect either. Replacing `_` with `Int` seems to be the only obvious way to make the problem disappear. Alas that defeats the point of using partial type signatures or typed holes in the first place.
New description: Consider the following program. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction, PartialTypeSignatures #-} module Main where import Text.Parsec import Text.Parsec.String parser :: Parser _ parser = read <$> many digit data Wrapper = Wrapper Int deriving Show wrapperParser = Wrapper <$> parser main :: IO () main = parseTest wrapperParser "0" }}} I am not sure whether it is valid or not, but it breaks the type checker as follows. {{{#!hs Main.hs:9:1: No instance for (Read w_) When checking that ‘parser’ has the specified type parser :: forall w_. Parser w_ Probable cause: the inferred type is ambiguous Main.hs:13:29: Couldn't match type ‘w_’ with ‘Int’ ‘w_’ is untouchable inside the constraints () bound by the inferred type of wrapperParser :: ParsecT String () Data.Functor.Identity.Identity Wrapper at Main.hs:13:1-34ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): No skolem info: w__a2BN[sk] }}} Disabling `PartialTypeSignatures` makes no difference. Switching from `parsec` to `megaparsec` and changing `many digit` to `some digitChar` does not have an effect either. Removing `NoMonomorphismRestriction` makes the problem disappear, as does changing `_` to `Int`. The libraries used were * `array-0.5.1.0`, * `base-4.8.1.0`, * `binary-0.7.5.0`, * `bytestring-0.10.6.0`, * `containers-0.5.6.2`, * `deepseq-1.4.1.1`, * `ghc-prim-0.4.0.0`, * `integer-gmp-1.0.0.0`, * `megaparsec-4.1.1`, * `mtl-2.2.1`, * `parsec-3.1.9`, * `text-1.2.1.3` and * `transformers-0.4.2.0`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate * related: => #10615 Comment: This looks like a duplicate of #10615. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Here is a self-contained reproducer. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE PartialTypeSignatures #-} module T11122 where data Parser a instance Functor Parser where fmap = undefined many p = undefined digit = undefined parseTest = undefined -------------------------------------------- parser :: Parser _ --parser :: Parser Int parser = read <$> many digit data Wrapper = Wrapper Int deriving Show wrapperParser = Wrapper <$> parser main :: IO () main = parseTest wrapperParser "0" }}} This is the error message that HEAD generates: {{{ $ ghc-7.11.20151123 Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) Test.hs:21:1: error: No instance for (Read t) When checking that ‘parser’ has the inferred type parser :: forall t. Parser t Probable cause: the inferred type is ambiguous Test.hs:28:18: error: Ambiguous type variable ‘f0’ arising from a use of ‘wrapperParser’ prevents the constraint ‘(Functor f0)’ from being solved. Probable fix: use a type annotation to specify what ‘f0’ should be. These potential instances exist: instance Functor (Array i) -- Defined in ‘GHC.Arr’ instance Functor IO -- Defined in ‘GHC.Base’ instance Functor Parser -- Defined at Test.hs:8:10 ...plus four others (use -fprint-potential-instances to see them all) In the first argument of ‘parseTest’, namely ‘wrapperParser’ In the expression: parseTest wrapperParser "0" In an equation for ‘main’: main = parseTest wrapperParser "0" }}} I don't know if that means the problem is fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: duplicate => Comment: In `wip/spj-wildcard-refactor` (shortly to land) I get {{{ T11122.hs:18:18: warning: • Found type wildcard ‘_’ standing for ‘Int’ • In the type signature: parser :: Parser _ • Relevant bindings include parser :: Parser Int (bound at T11122.hs:20:1) }}} Which looks right. Ben: can you add this as a regression test please when you land that big patch? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => bgamari -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Added testcase in Phab:D1655 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic
-------------------------------------+-------------------------------------
Reporter: tuplanolla | Owner: bgamari
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: | Keywords:
Operating System: Linux | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #10615 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11122: Ambiguous inferred type causes a panic -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_fail/T11122 Blocked By: | Blocking: Related Tickets: #10615 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => partial-sigs/should_fail/T11122 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11122#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC