[GHC] #10340: Type inference regression with Any
GHC
ghc-devs at haskell.org
Tue Apr 21 23:58:49 UTC 2015
#10340: Type inference regression with Any
-------------------------------------+-------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
(Type checker) | Operating System: Unknown/Multiple
Keywords: | Type of failure: GHC rejects
Architecture: | valid program
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The following module typechecks with GHC 7.8.3, but GHC 7.10.1 gives an
error:
{{{#!hs
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Foo where
import GHC.Exts (Any)
class MonadState s m where
get :: m s
newtype State s a = State (s -> (s, a))
instance MonadState s (State s) where
get = State $ \s -> (s, s)
foo :: State Any Any
foo = get
}}}
{{{
[1 of 1] Compiling Foo ( any.hs, any.o )
any.hs:15:7:
No instance for (MonadState Any (State Any))
arising from a use of ‘get’
In the expression: get
In an equation for ‘foo’: foo = get
}}}
If I replace the uses of `Any` with `Int`, the problem goes away.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10340>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list