[GHC] #11608: Possible type-checker regression in GHC 8.0 when compiling `microlens`
GHC
ghc-devs at haskell.org
Sat Feb 20 01:09:33 UTC 2016
#11608: Possible type-checker regression in GHC 8.0 when compiling `microlens`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version:
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Specifically, the issue seems to pertain to type equalities in default
signatures in typeclasses. Here is the failing code, reduced to
reproducible examples:
From [http://hackage.haskell.org/package/microlens-0.4.2.0/docs/src/Lens-
Micro-Internal.html#line-184 microlens]:
{{{#!hs
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
each :: Traversal s t a b
default each :: (Traversable g, s ~ g a, t ~ g b) => Traversal s t a b
each = traverse
}}}
From [http://hackage.haskell.org/package/free-4.12.4/docs/src/Control-
Monad-Free-Class.html#line-106 free]:
{{{#!hs
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
class MonadTrans t where
lift :: Monad m => m a -> t m a
class Monad m => MonadFree f m | m -> f where
wrap :: f (m a) -> m a
default wrap :: (m ~ t n, MonadTrans t, MonadFree f n, Functor f) => f
(m a) -> m a
wrap = join . lift . wrap . fmap return
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11608#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list