[GHC] #10079: Coercible solver regression: Couldn't match rep of () with Const () b
GHC
ghc-devs at haskell.org
Wed Feb 11 07:36:23 UTC 2015
#10079: Coercible solver regression: Couldn't match rep of () with Const () b
-------------------------------------+-------------------------------------
Reporter: glguy | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1-rc1
checker) | Keywords:
Resolution: | Architecture:
Operating System: Unknown/Multiple | Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | Blocking:
Blocked By: | Differential Revisions:
Related Tickets: |
-------------------------------------+-------------------------------------
Description changed by glguy:
Old description:
> Hello, I ran into what appears to be a regression in the Coercible solver
> since 7.8.4. This is as small as I've managed to get my example case.
>
> {{{
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE FunctionalDependencies #-}
> {-# LANGUAGE FlexibleContexts #-}
> module Bug where
>
> import Control.Applicative
> import Data.Coerce
>
> broken :: Bizarre (->) w => w a b t -> ()
> broken = getConst #. bazaar (Const #. const ())
>
> class Profunctor p where
> (#.) :: Coercible c b => (b -> c) -> p a b -> p a c
>
> class Bizarre p w | w -> p where
> bazaar :: Applicative f => p a (f b) -> w a b t -> f t
> }}}
>
> {{{
> Bug.hs:10:36:
> Couldn't match representation of type ‘()’
> with that of ‘Const () b’
> Relevant role signatures: type role Const representational phantom
> Relevant bindings include
> broken :: w a b t -> () (bound at Bug.hs:10:1)
> In the first argument of ‘bazaar’, namely ‘(Const #. const ())’
> In the second argument of ‘(#.)’, namely
> ‘bazaar (Const #. const ())’
> In the expression: getConst #. bazaar (Const #. const ())
> }}}
New description:
Hello, I ran into what appears to be a regression in the Coercible solver
since 7.8.4. This is as small as I've managed to get my example case.
{{{
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
module Bug where
import Control.Applicative
import Data.Coerce
broken :: Bizarre (->) w => w a b t -> ()
broken = getConst #. bazaar (Const #. const ())
class Profunctor p where
(#.) :: Coercible c b => (b -> c) -> p a b -> p a c
instance Profunctor (->) where
(#.) = (.)
class Bizarre p w | w -> p where
bazaar :: Applicative f => p a (f b) -> w a b t -> f t
}}}
{{{
Bug.hs:10:36:
Couldn't match representation of type ‘()’
with that of ‘Const () b’
Relevant role signatures: type role Const representational phantom
Relevant bindings include
broken :: w a b t -> () (bound at Bug.hs:10:1)
In the first argument of ‘bazaar’, namely ‘(Const #. const ())’
In the second argument of ‘(#.)’, namely
‘bazaar (Const #. const ())’
In the expression: getConst #. bazaar (Const #. const ())
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10079#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list