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

GHC ghc-devs at haskell.org
Mon Nov 23 10:50:03 UTC 2015


#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


More information about the ghc-tickets mailing list