[GHC] #11122: Ambiguous inferred type causes a panic
GHC
ghc-devs at haskell.org
Sun Nov 22 17:29:38 UTC 2015
#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
More information about the ghc-tickets
mailing list