[GHC] #10770: Typeable solver has strange effects
GHC
ghc-devs at haskell.org
Wed Aug 12 21:28:24 UTC 2015
#10770: Typeable solver has strange effects
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by thomie):
* component: Compiler => Compiler (Type checker)
Comment:
I get the same error with HEAD (ghc-7.11.20150809), and also notice the
following:
{{{#!haskell
{-# LANGUAGE FlexibleContexts #-}
module Test where
import Data.Typeable
f :: (Typeable a, Typeable (Maybe a)) => Maybe a -> TypeRep
f x = let k = typeOf x in k
}}}
shows the warning:
{{{
Redundant constraint: Typeable (Maybe a)
}}}
Whereas the same program, with the last line changed to:
{{{#!haskell
f x = typeOf x
}}}
shows
{{{
Redundant constraint: Typeable a
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10770#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list