[GHC] #13598: role annotation for newtype (partially?) ignored?
GHC
ghc-devs at haskell.org
Thu Apr 20 14:25:02 UTC 2017
#13598: role annotation for newtype (partially?) ignored?
-------------------------------------+-------------------------------------
Reporter: edsko | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
A constraint `Coercible o (T a)` is ambiguous if the role of `a` is
representational (provided `a` is not otherwise constrained, of course),
but unambiguous if `a` is a phantom type:
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RoleAnnotations #-}
module CoerceTest where
import Data.Coerce
type role A phantom
data A a = MkA Int
type role B representational
data B a = MkB Int
-- accepted by the type checker (as it should be)
fooA :: Coercible o (A a) => o -> ()
fooA _ = ()
-- rejected by the type checker (as it should be) with
-- "Couldn't match representation of type ‘a0’ with that of ‘a’"
-- fooB :: Coercible o (B a) => o -> ()
-- fooB _ = ()
}}}
However, for `newtype`s something odd happens:
{{{#!hs
type role C representational
newtype C a = MkC Int
-- accepted by the type checker (but should not be)
fooC :: Coercible o (C a) => o -> ()
fooC _ = ()
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13598>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list