[GHC] #10285: Bug in Coerciible
GHC
ghc-devs at haskell.org
Fri Apr 10 15:19:33 UTC 2015
#10285: Bug in Coerciible
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 7.10.2
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Richard and I uncovered this
{{{
{-# LANGUAGE RoleAnnotations #-}
module Bar( N ) where -- Data constructor not exported
type role N representational
newtype N a = MkN Int
}}}
and
{{{
{-# LANGUAGE FlexibleContexts #-}
module Foo where
import Data.Coerce
import Data.Type.Coercion
import Bar
f :: Coercible (N a) (N b) => Coercion a b
f = Coercion
}}}
This compiles but it should not! It wrongly compiles by using `nth (N a
~R N b)`; but (as Fig 4 of [http://research.microsoft.com/en-
us/um/people/simonpj/papers/ext-f/ the Corcible paper] says), we can't
decompose a newtype at representational role.
Easy to fix.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10285>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list