[GHC] #7594: GHCi becomes confused about IO type

#7594: GHCi becomes confused about IO type -----------------------------+---------------------------------------------- Reporter: Khudyakov | Owner: Type: bug | Status: new Priority: normal | Component: GHCi Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE Rank2Types #-} import GHC.Prim (Constraint) class (c1 t, c2 t) => (:&:) (c1 :: * -> Constraint) (c2 :: * -> Constraint) (t :: *) instance (c1 t, c2 t) => (:&:) c1 c2 t data ColD c where ColD :: (c a) => a -> ColD c app :: (forall a. (c a) => a -> b) -> ColD c -> b app f (ColD x) = f x q :: ColD (Show :&: Real) q = ColD (1.2 :: Double) }}} In the interactive mode it's possible to confuse GHCi about IO type. It tries to show expression instread of executing it. {{{ *Main> app print q <interactive>:3:1: No instance for (Show (IO ())) arising from a use of `print' Possible fix: add an instance declaration for (Show (IO ())) In a stmt of an interactive GHCi command: print it }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7594 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7594: GHCi becomes confused about IO type -------------------------------+-------------------------------------------- Reporter: Khudyakov | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.6.1 Resolution: worksforme | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- Changes (by simonpj): * status: new => closed * difficulty: => Unknown * resolution: => worksforme Comment: Hmm. Absolutely right, and this happens for 7.6.2 too. However with HEAD we get: {{{ <interactive>:2:5: Couldn't match type `b' with `IO ()' `b' is untouchable inside the constraints ((:&:) Show Real a) bound by a type expected by the context: (:&:) Show Real a => a -> b at <interactive>:2:1-11 `b' is a rigid type variable bound by the inferred type of it :: b at <interactive>:2:1 }}} This is actually right, although the error message is not so easy. We know that {{{ print :: Show a => a -> IO () }}} We also know (by way of the argument `q`, that `c = (Show :&: Real) a`. So, to check that `print` is a valid argument to `app`, we must check that {{{ From (Show :&: Real) a prove that (Show a, beta ~ IO ()) }}} where `beta` is a unification variable (as-yet-unknown type) obtained by instantiating `app`. Well, you say, we can choose `beta` to be `IO ()` and we are done. But not so: in general the "`From`" constraints might include GADT-style equalites, and GHC is careful NOT to unify under equality constraints. (See the [http://haskell.org/haskellwiki/Simonpj/Talk:OutsideIn Modular type inference with local assumptions] paper.) That's why `beta` is "untouchable". Easily fixed by saying `app print q :: IO ()`, and that works fine. I am strongly dis-inclined to attempt to find out what's happening in 7.6! So I propose just to close this. I might add a regression test though. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7594#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7594: GHCi becomes confused about IO type -------------------------------+-------------------------------------------- Reporter: Khudyakov | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.6.1 Resolution: worksforme | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: polykinds/T7594 | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- Changes (by simonpj): * testcase: => polykinds/T7594 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7594#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC