
#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