[GHC] #10079: Coercible solver regression: Couldn't match rep of () with Const () b
GHC
ghc-devs at haskell.org
Wed Feb 11 07:34:29 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 | Version: 7.10.1-rc1
(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: |
-------------------------------------+-------------------------------------
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 ())
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10079>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list