[GHC] #8889: GHCI reports nasty type signatures

#8889: GHCI reports nasty type signatures ----------------------------------+------------------------------ Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.1-rc1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: Other Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ----------------------------------+------------------------------ Load a file that contains: {{{ {-# LANGUAGE TypeFamilies , ConstraintKinds , MultiParamTypeClasses , UndecidableInstances , FlexibleInstances #-} import GHC.Prim import Prelude hiding (Functor(..)) class Functor f where type C_fmap_a f a :: Constraint type C_fmap_a f a = () type C_fmap_b f b :: Constraint type C_fmap_b f b = () fmap :: (C_fmap_a f a, C_fmap_b f b) => (a -> b) -> f a -> f b fmap1 :: (ValidFunctor f a, ValidFunctor f b) => (a -> b) -> f a -> f b fmap2 :: (ValidFunctor' f a, ValidFunctor' f b) => (a -> b) -> f a -> f b type ValidFunctor f a = ( Functor f , C_fmap_a f a , C_fmap_b f a ) class ValidFunctor f a => ValidFunctor' f a instance ValidFunctor f a => ValidFunctor' f a }}} Then check the following types in ghci {{{ ghci> :t fmap fmap :: (t, t1, Functor f, C_fmap_b f b ~ t1, C_fmap_a f a ~ t) => (a -> b) -> f a -> f b ghci> :t fmap1 fmap1 :: (t, t1, t2, t3, Functor f, C_fmap_b f b ~ t3, C_fmap_b f a ~ t1, C_fmap_a f b ~ t2, C_fmap_a f a ~ t) => (a -> b) -> f a -> f b ghci> :t fmap2 fmap2 :: (t, t1, t2, t3, Functor f, C_fmap_b f b ~ t3, C_fmap_b f a ~ t1, C_fmap_a f b ~ t2, C_fmap_a f a ~ t) => (a -> b) -> f a -> f b }}} These types are much nastier looking than they need to be. There are two problems: 1) Bogus types t,t1,t2,t3 are introduced when they don't need to be. This is confuses the type signatures quite a bit. 2) The type alias ValidFunctor is being desugared in the type signature for fmap1. This makes type aliases for constraints rather pointless. Also, I tried to solve problem two by adding an extra class, and hoping the class would be displayed instead, but this still doesn't work. I assume this is actually intended behavior though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8889 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8889: GHCI reports nasty type signatures
--------------------------------+----------------------------------
Reporter: MikeIzbicki | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.8.1-rc1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: Other | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
--------------------------------+----------------------------------
Comment (by Simon Peyton Jones

#8889: GHCI reports nasty type signatures
--------------------------------+----------------------------------
Reporter: MikeIzbicki | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.8.1-rc1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64 (amd64)
Type of failure: Other | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
--------------------------------+----------------------------------
Comment (by Simon Peyton Jones

#8889: GHCI reports nasty type signatures -------------------------------------------------+------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: GHCi | Version: Resolution: | 7.8.1-rc1 Operating System: Linux | Keywords: Type of failure: Other | Architecture: Test Case: | x86_64 (amd64) indexed_types/should_compile/T8889 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => merge * testcase: => indexed_types/should_compile/T8889 Comment: Excellent point, thank you. Fixed, with a regression test. Could be merged if there is time, but not a big deal. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8889#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8889: GHCI reports nasty type signatures -------------------------------------------------+------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: Priority: normal | closed Component: GHCi | Milestone: 7.8.1 Resolution: fixed | Version: Operating System: Linux | 7.8.1-rc2 Type of failure: Other | Keywords: Test Case: | Architecture: indexed_types/should_compile/T8889 | x86_64 (amd64) Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: merge => closed * version: 7.8.1-rc1 => 7.8.1-rc2 * resolution: => fixed * milestone: => 7.8.1 Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8889#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC